1 /*  Part of SWI-Prolog
2 
3     Author:        Jan Wielemaker
4     E-mail:        J.Wielemaker@vu.nl
5     WWW:           http://www.swi-prolog.org
6     Copyright (c)  2000-2020, University of Amsterdam
7                               Vu University Amsterdam
8     All rights reserved.
9 
10     Redistribution and use in source and binary forms, with or without
11     modification, are permitted provided that the following conditions
12     are met:
13 
14     1. Redistributions of source code must retain the above copyright
15        notice, this list of conditions and the following disclaimer.
16 
17     2. Redistributions in binary form must reproduce the above copyright
18        notice, this list of conditions and the following disclaimer in
19        the documentation and/or other materials provided with the
20        distribution.
21 
22     THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
23     "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
24     LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
25     FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
26     COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
27     INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
28     BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
29     LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
30     CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
31     LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
32     ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
33     POSSIBILITY OF SUCH DAMAGE.
34 */
35 
36 #ifndef _SWI_CPP_H
37 #define _SWI_CPP_H
38 
39 #include <SWI-Prolog.h>
40 #include <string.h>
41 #include <wchar.h>
42 #if !(defined(__APPLE__) || defined(__FreeBSD__))
43 #include <stdlib.h>
44 #endif
45 
46 #ifdef __BORLANDC__
47 #define __inline inline
48 #endif
49 
50 /* Define as 1 if undefined or defined as empty */
51 #if !defined(PL_ARITY_AS_SIZE) || (0-PL_ARITY_AS_SIZE-1)==1
52 #undef PL_ARITY_AS_SIZE
53 #define PL_ARITY_AS_SIZE 1
54 #endif
55 
56 #ifndef ARITY_T
57 #if PL_ARITY_AS_SIZE
58 #define ARITY_T size_t
59 #else
60 #define ARITY_T int
61 #endif
62 #endif
63 
64 class PlTerm;
65 class PlTermv;
66 
67 		 /*******************************
68 		 *	 PROLOG CONSTANTS	*
69 		 *******************************/
70 
71 class PlFunctor
72 {
73 public:
74   functor_t functor;
75 
PlFunctor(const char * name,ARITY_T arity)76   PlFunctor(const char *name, ARITY_T arity)
77   { functor = PL_new_functor(PL_new_atom(name), arity);
78   }
PlFunctor(const wchar_t * name,ARITY_T arity)79   PlFunctor(const wchar_t *name, ARITY_T arity)
80   { functor = PL_new_functor(PL_new_atom_wchars(wcslen(name), name), arity);
81   }
82 };
83 
84 
85 class PlAtom
86 {
87 public:
88   atom_t handle;
89 
PlAtom(atom_t h)90   PlAtom(atom_t h)
91   { handle = h;
92   }
PlAtom(const char * text)93   PlAtom(const char *text)
94   { handle = PL_new_atom(text);
95   }
PlAtom(const wchar_t * text)96   PlAtom(const wchar_t *text)
97   { handle = PL_new_atom_wchars(wcslen(text), text);
98   }
99   PlAtom(const PlTerm &t);
100 
101   operator const char *(void) const
102   { return PL_atom_chars(handle);
103   }
104   operator const wchar_t *(void) const
105   { return PL_atom_wchars(handle, NULL);
106   }
107 
108   int operator ==(const char *s) const
109   { return strcmp(s, PL_atom_chars(handle)) == 0;
110   }
111   int operator ==(const wchar_t *s) const
112   { return wcscmp(s, PL_atom_wchars(handle, NULL)) == 0;
113   }
114   int operator ==(const PlAtom &a) const
115   { return handle == a.handle;
116   }
117   int operator ==(atom_t to) const
118   { return handle == to;
119   }
120 };
121 
122 		 /*******************************
123 		 *     GENERIC PROLOG TERM	*
124 		 *******************************/
125 
126 
127 class PlTerm
128 {
129 public:
130   term_t ref;
131 
132   PlTerm();
PlTerm(const PlTerm & other)133   PlTerm(const PlTerm &other) : ref(other.ref) {}
PlTerm(term_t t)134   PlTerm(term_t t)
135   { ref = t;
136   }
137 
138 					/* C --> PlTerm */
139   PlTerm(const char *text);
140   PlTerm(const wchar_t *text);
141   PlTerm(long val);
142   PlTerm(double val);
143   PlTerm(const PlAtom &a);
144   PlTerm(void *ptr);
145 
146 					/* PlTerm --> C */
term_t(void)147   operator term_t(void) const
148   { return ref;
149   }
150   operator char *(void) const;
151   operator wchar_t *(void) const;
152   operator long(void) const;
153   operator int(void) const;
154   operator double(void) const;
155   operator PlAtom(void) const;
156   operator void *(void) const;
157 
type()158   int type() const
159   { return PL_term_type(ref);
160   }
161 
162 					/* Compounds */
163   PlTerm operator [](ARITY_T index) const;
164   ARITY_T arity() const;
165   const char *name() const;
166 
167 					/* UNIFY */
168   int operator =(const PlTerm &t2);	/* term */
169   int operator =(const PlAtom &a);	/* atom */
170   int operator =(const char *v);	/* atom (from char *) */
171   int operator =(const wchar_t *v);	/* atom (from wchar_t *) */
172   int operator =(long v);		/* integer */
173   int operator =(int v);		/* integer */
174   int operator =(double v);		/* float */
175   int operator =(const PlFunctor &f);	/* functor */
176 
177 					/* Comparison standard order terms */
178   int operator ==(const PlTerm &t2) const
179   { return PL_compare(ref, t2.ref) == 0;
180   }
181   int operator !=(const PlTerm &t2) const
182   { return PL_compare(ref, t2.ref) != 0;
183   }
184   int operator <(const PlTerm &t2) const
185   { return PL_compare(ref, t2.ref) < 0;
186   }
187   int operator >(const PlTerm &t2) const
188   { return PL_compare(ref, t2.ref) > 0;
189   }
190   int operator <=(const PlTerm &t2) const
191   { return PL_compare(ref, t2.ref) <= 0;
192   }
193   int operator >=(const PlTerm &t2) const
194   { return PL_compare(ref, t2.ref) >= 0;
195   }
196 					/* comparison (long) */
197   int operator ==(long v) const;
198   int operator !=(long v) const;
199   int operator <(long v) const;
200   int operator >(long v) const;
201   int operator <=(long v) const;
202   int operator >=(long v) const;
203 
204 					/* comparison (string) */
205   int operator ==(const char *s) const;
206   int operator ==(const wchar_t *s) const;
207   int operator ==(const PlAtom &a) const;
208 };
209 
210 
211 		 /*******************************
212 		 *	   TERM VECTOR		*
213 		 *******************************/
214 
215 class PlTermv
216 {
217 public:
218   term_t a0;
219   int    size;
220 
PlTermv(int n)221   PlTermv(int n)
222   { a0   = PL_new_term_refs(n);
223     size = n;
224   }
PlTermv(int n,term_t t0)225   PlTermv(int n, term_t t0)
226   { a0   = t0;
227     size = n;
228   }
229 
230 					/* create from args */
231   PlTermv(PlTerm m0);
232   PlTermv(PlTerm m0, PlTerm m1);
233   PlTermv(PlTerm m0, PlTerm m1, PlTerm m2);
234   PlTermv(PlTerm m0, PlTerm m1, PlTerm m2, PlTerm m3);
235   PlTermv(PlTerm m0, PlTerm m1, PlTerm m2, PlTerm m3, PlTerm m4);
236 
237   PlTerm operator [](int n) const;
238 };
239 
240 		 /*******************************
241 		 *	 SPECIALISED TERMS	*
242 		 *******************************/
243 
244 class PlCompound : public PlTerm
245 {
246 public:
247 
248   PlCompound(const char *text);
249   PlCompound(const wchar_t *text);
250   PlCompound(const char *functor, const PlTermv &args);
251   PlCompound(const wchar_t *functor, const PlTermv &args);
252 };
253 
254 
255 class PlString : public PlTerm
256 {
257 public:
258 
259   PlString(const char *text);
260   PlString(const char *text, size_t len);
261   PlString(const wchar_t *text);
262   PlString(const wchar_t *text, size_t len);
263 };
264 
265 
266 class PlCodeList : public PlTerm
267 {
268 public:
269 
270   PlCodeList(const char *text);
271   PlCodeList(const wchar_t *text);
272 };
273 
274 
275 class PlCharList : public PlTerm
276 {
277 public:
278 
279   PlCharList(const char *text);
280   PlCharList(const wchar_t *text);
281 };
282 
283 
284 		 /*******************************
285 		 *	      EXCEPTIONS	*
286 		 *******************************/
287 
288 class PlException : public PlTerm
289 {
290 public:
PlException()291   PlException()
292   { term_t ex = PL_exception(0);
293     if ( ex )
294       ref = ex;
295     else
296       PL_fatal_error("No exception");
297   }
298 
PlException(const PlTerm & t)299   PlException(const PlTerm &t)
300   { ref = t.ref;
301   }
302 
303   operator const char *(void);
304   operator const wchar_t *(void);
305 
plThrow()306   int plThrow()
307   { return PL_raise_exception(ref);
308   }
309 
310   void cppThrow();
311 };
312 
313 
314 class PlTypeError : public PlException
315 {
316 public:
317 
PlTypeError(const PlTerm & t)318   PlTypeError(const PlTerm &t) : PlException(t) {}
319 
PlTypeError(const char * expected,PlTerm actual)320   PlTypeError(const char *expected, PlTerm actual) :
321     PlException(PlCompound("error",
322 			   PlTermv(PL_is_variable(actual.ref) ?
323 				     PlTerm("instantiation_error") :
324 				     PlCompound("type_error",
325 						PlTermv(expected, actual)),
326 				   PlTerm())))
327   {
328   }
329 };
330 
331 
332 class PlDomainError : public PlException
333 {
334 public:
335 
PlDomainError(const PlTerm & t)336   PlDomainError(const PlTerm &t) : PlException(t) {}
337 
PlDomainError(const char * expected,PlTerm actual)338   PlDomainError(const char *expected, PlTerm actual) :
339     PlException(PlCompound("error",
340 			   PlTermv(PlCompound("domain_error",
341 					      PlTermv(expected, actual)),
342 				   PlTerm())))
343   {
344   }
345 };
346 
347 
348 class PlInstantiationError : public PlException
349 {
350 public:
351 
PlInstantiationError(const PlTerm & t)352   PlInstantiationError(const PlTerm &t) :
353   PlException(PL_is_variable(t) ?
354 	      PlCompound("error",
355 			 PlTermv("instantiation_error",
356 				 t)) : t) {}
357 
PlInstantiationError()358   PlInstantiationError() :
359     PlException(PlCompound("error",
360 			   PlTermv("instantiation_error",
361 				   PlTerm())))
362   {
363   }
364 };
365 
366 
367 class PlExistenceError : public PlException
368 {
369 public:
370 
PlExistenceError(const PlTerm & t)371   PlExistenceError(const PlTerm &t) : PlException(t) {}
372 
PlExistenceError(const char * type,PlTerm actual)373   PlExistenceError(const char *type, PlTerm actual) :
374     PlException(PlCompound("error",
375 			   PlTermv(PlCompound("existence_error",
376 					      PlTermv(type, actual)),
377 				   PlTerm())))
378   {
379   }
380 };
381 
382 
383 class PlPermissionError : public PlException
384 {
385 public:
386 
PlPermissionError(const PlTerm & t)387   PlPermissionError(const PlTerm &t) : PlException(t) {}
388 
PlPermissionError(const char * op,const char * type,PlTerm obj)389   PlPermissionError(const char *op, const char *type, PlTerm obj) :
390     PlException(PlCompound("error",
391 			   PlTermv(PlCompound("permission_error",
392 					      PlTermv(op, type, obj)),
393 				   PlTerm())))
394   {
395   }
396 };
397 
398 
399 class PlResourceError : public PlException
400 {
401 public:
PlResourceError()402   PlResourceError() : PlException() {}
403 
PlResourceError(const PlTerm & t)404   PlResourceError(const PlTerm &t) : PlException(t) {}
405 
PlResourceError(const char * resource)406   PlResourceError(const char *resource) :
407     PlException(PlCompound("error",
408 			   PlTermv(PlCompound("resource_error",
409 					      PlTermv(PlTerm(resource))),
410 				   PlTerm())))
411   {
412   }
413 };
414 
415 
416 class PlTermvDomainError : public PlException
417 {
418 public:
419 
PlTermvDomainError(int size,int n)420   PlTermvDomainError(int size, int n) :
421     PlException(PlCompound("error",
422 			   PlTermv(PlCompound("domain_error",
423 					      PlTermv(PlCompound("argv",
424 								 size),
425 						      PlTerm((long)n))),
426 				   PlTerm())))
427   {
428   }
429 };
430 
431 
432 		 /*******************************
433 		 *     PLTERM IMPLEMENTATION	*
434 		 *******************************/
435 
436 __inline
PlTerm()437 PlTerm::PlTerm()
438 { if ( !(ref = PL_new_term_ref()) )
439     throw PlResourceError();
440 }
441 
442 __inline
PlTerm(const char * text)443 PlTerm::PlTerm(const char *text)
444 { if ( !(ref = PL_new_term_ref()) ||
445        !PL_put_atom_chars(ref, text) )
446     throw PlResourceError();
447 }
448 
449 __inline
PlTerm(const wchar_t * text)450 PlTerm::PlTerm(const wchar_t *text)
451 { if ( !(ref = PL_new_term_ref()) ||
452        !PL_unify_wchars(ref, PL_ATOM, (size_t)-1, text) )
453     throw PlResourceError();
454 }
455 
456 __inline
PlTerm(long val)457 PlTerm::PlTerm(long val)
458 { if ( !(ref = PL_new_term_ref()) ||
459        !PL_put_integer(ref, val) )
460     throw PlResourceError();
461 }
462 
463 __inline
PlTerm(double val)464 PlTerm::PlTerm(double val)
465 { if ( !(ref = PL_new_term_ref()) ||
466        !PL_put_float(ref, val) )
467     throw PlResourceError();
468 }
469 
470 __inline
PlTerm(const PlAtom & a)471 PlTerm::PlTerm(const PlAtom &a)
472 { if ( !(ref = PL_new_term_ref()) )
473     throw PlResourceError();
474 
475   PL_put_atom(ref, a.handle);
476 }
477 
478 __inline
PlTerm(void * ptr)479 PlTerm::PlTerm(void *ptr)
480 { if ( !(ref = PL_new_term_ref()) ||
481        !PL_put_pointer(ref, ptr) )
482     throw PlResourceError();
483 }
484 
485 		 /*******************************
486 		 *  SPECIALISED IMPLEMENTATIONS *
487 		 *******************************/
488 
489 __inline
PlString(const char * text)490 PlString::PlString(const char *text) : PlTerm()
491 { if ( !PL_put_string_chars(ref, text) )
492     throw PlResourceError();
493 }
494 
495 __inline
PlString(const char * text,size_t len)496 PlString::PlString(const char *text, size_t len) : PlTerm()
497 { if ( !PL_put_string_nchars(ref, len, text) )
498     throw PlResourceError();
499 }
500 
501 __inline
PlString(const wchar_t * text)502 PlString::PlString(const wchar_t *text) : PlTerm()
503 { if ( !PL_unify_wchars(ref, PL_STRING, (size_t)-1, text) )
504     throw PlResourceError();
505 }
506 
507 __inline
PlString(const wchar_t * text,size_t len)508 PlString::PlString(const wchar_t *text, size_t len) : PlTerm()
509 { if ( !PL_unify_wchars(ref, PL_STRING, len, text) )
510     throw PlResourceError();
511 }
512 
513 __inline
PlCodeList(const char * text)514 PlCodeList::PlCodeList(const char *text) : PlTerm()
515 { if ( !PL_put_list_codes(ref, text) )
516     throw PlResourceError();
517 }
518 
519 __inline
PlCharList(const char * text)520 PlCharList::PlCharList(const char *text) : PlTerm()
521 { if ( !PL_put_list_chars(ref, text) )
522     throw PlResourceError();
523 }
524 
525 __inline
PlCodeList(const wchar_t * text)526 PlCodeList::PlCodeList(const wchar_t *text) : PlTerm()
527 { if ( !PL_unify_wchars(ref, PL_CODE_LIST, (size_t)-1, text) )
528     throw PlResourceError();
529 }
530 
531 __inline
PlCharList(const wchar_t * text)532 PlCharList::PlCharList(const wchar_t *text) : PlTerm()
533 { if ( !PL_unify_wchars(ref, PL_CHAR_LIST, (size_t)-1, text) )
534     throw PlResourceError();
535 }
536 
537 
538 		 /*******************************
539 		 *             LISTS		*
540 		 *******************************/
541 
542 class PlTail : public PlTerm
543 {
544 public:
545 
PlTail(const PlTerm & l)546   PlTail(const PlTerm &l)
547   { if ( PL_is_variable(l.ref) || PL_is_list(l.ref) )
548     { if ( !(ref = PL_copy_term_ref(l.ref)) )
549 	throw PlResourceError();
550     } else
551       throw PlTypeError("list", l.ref);
552   }
553 
554 					/* building */
append(const PlTerm & e)555   int append(const PlTerm &e)
556   { term_t tmp, ex;
557 
558     if ( (tmp = PL_new_term_ref()) &&
559 	 PL_unify_list(ref, tmp, ref) &&
560 	 PL_unify(tmp, e.ref) )
561     { PL_reset_term_refs(tmp);
562       return TRUE;
563     }
564 
565     if ( (ex = PL_exception(0)) )
566       throw PlResourceError(ex);
567 
568     return FALSE;
569   }
close()570   int close()
571   { return PL_unify_nil(ref);
572   }
573 
574 					/* enumerating */
next(PlTerm & t)575   int next(PlTerm &t)
576   { if ( PL_get_list(ref, t, ref) )
577       return TRUE;
578 
579     if ( PL_get_nil(ref) )
580       return FALSE;
581 
582     throw PlTypeError("list", ref);
583   }
584 };
585 
586 
587 		 /*******************************
588 		 *	     REGISTER		*
589 		 *******************************/
590 
591 
592 class PlRegister
593 {
594 public:
595 
PlRegister(const char * module,const char * name,int arity,foreign_t (f)(term_t t0,int a,control_t ctx))596   PlRegister(const char *module, const char *name, int arity,
597 	    foreign_t (f)(term_t t0, int a, control_t ctx))
598   { PL_register_foreign_in_module(module, name, arity, reinterpret_cast<pl_function_t>(f), PL_FA_VARARGS);
599   }
600 
PlRegister(const char * module,const char * name,foreign_t (* f)(PlTerm a0))601   PlRegister(const char *module, const char *name, foreign_t (*f)(PlTerm a0))
602   { PL_register_foreign_in_module(module, name, 1, reinterpret_cast<pl_function_t>(f), 0);
603   }
PlRegister(const char * module,const char * name,foreign_t (* f)(PlTerm a0,PlTerm a1))604   PlRegister(const char *module, const char *name, foreign_t (*f)(PlTerm a0, PlTerm a1))
605   { PL_register_foreign_in_module(module, name, 2, reinterpret_cast<pl_function_t>(f), 0);
606   }
PlRegister(const char * module,const char * name,foreign_t (* f)(PlTerm a0,PlTerm a1,PlTerm a2))607   PlRegister(const char *module, const char *name, foreign_t (*f)(PlTerm a0, PlTerm a1, PlTerm a2))
608   { PL_register_foreign_in_module(module, name, 3, reinterpret_cast<pl_function_t>(f), 0);
609   }
610 
611   // for non-deterministic calls
PlRegister(const char * module,const char * name,int arity,foreign_t (f)(term_t t0,int a,control_t ctx),short flags)612   PlRegister(const char *module, const char *name, int arity,
613              foreign_t (f)(term_t t0, int a, control_t ctx), short flags)
614   { PL_register_foreign_in_module(module, name, arity, reinterpret_cast<pl_function_t>(f), flags);
615   }
616 };
617 
618 
619 		 /*******************************
620 		 *	 CALLING PROLOG		*
621 		 *******************************/
622 
623 class PlFrame
624 {
625 public:
626   fid_t fid;
627 
PlFrame()628   PlFrame()
629   { fid = PL_open_foreign_frame();
630   }
631 
~PlFrame()632   ~PlFrame()
633   { PL_close_foreign_frame(fid);
634   }
635 
rewind()636   void rewind()
637   { PL_rewind_foreign_frame(fid);
638   }
639 };
640 
641 
642 class PlQuery
643 {
644 public:
645   qid_t qid;
646 
PlQuery(predicate_t pred,const PlTermv & av)647   PlQuery(predicate_t pred, const PlTermv &av)
648   { qid = PL_open_query((module_t)0, PL_Q_PASS_EXCEPTION, pred, av.a0);
649     if ( !qid )
650       throw PlResourceError();
651   }
PlQuery(const char * name,const PlTermv & av)652   PlQuery(const char *name, const PlTermv &av)
653   { predicate_t p = PL_predicate(name, av.size, "user");
654 
655     qid = PL_open_query((module_t)0, PL_Q_PASS_EXCEPTION, p, av.a0);
656     if ( !qid )
657       throw PlResourceError();
658   }
PlQuery(const char * module,const char * name,const PlTermv & av)659   PlQuery(const char *module, const char *name, const PlTermv &av)
660   { atom_t ma = PL_new_atom(module);
661     atom_t na = PL_new_atom(name);
662     module_t m = PL_new_module(ma);
663     predicate_t p = PL_pred(PL_new_functor(na, av.size), m);
664 
665     PL_unregister_atom(ma);
666     PL_unregister_atom(na);
667 
668     qid = PL_open_query(m, PL_Q_PASS_EXCEPTION, p, av.a0);
669     if ( !qid )
670       throw PlResourceError();
671   }
672 
~PlQuery()673   ~PlQuery()
674   { if ( qid )
675       PL_cut_query(qid);
676   }
677 
678   int next_solution();
679 };
680 
681 
682 __inline int
PlCall(const char * predicate,const PlTermv & args)683 PlCall(const char *predicate, const PlTermv &args)
684 { PlQuery q(predicate, args);
685   return q.next_solution();
686 }
687 
688 __inline int
PlCall(const char * module,const char * predicate,const PlTermv & args)689 PlCall(const char *module, const char *predicate, const PlTermv &args)
690 { PlQuery q(module, predicate, args);
691   return q.next_solution();
692 }
693 
694 __inline int
PlCall(const char * goal)695 PlCall(const char *goal)
696 { PlQuery q("call", PlTermv(PlCompound(goal)));
697   return q.next_solution();
698 }
699 
700 __inline int
PlCall(const wchar_t * goal)701 PlCall(const wchar_t *goal)
702 { PlQuery q("call", PlTermv(PlCompound(goal)));
703   return q.next_solution();
704 }
705 
706 
707 
708 		 /*******************************
709 		 *	    ATOM (BODY)		*
710 		 *******************************/
711 
712 __inline
PlAtom(const PlTerm & t)713 PlAtom::PlAtom(const PlTerm &t)
714 { atom_t a;
715 
716   if ( PL_get_atom(t.ref, &a) )
717     handle = a;
718   else
719     throw PlTypeError("atom", t);
720 }
721 
722 
723 		 /*******************************
724 		 *	    TERM (BODY)		*
725 		 *******************************/
726 
727 					/* PlTerm --> C */
728 
729 __inline PlTerm::operator char *(void) const
730 { char *s;
731 
732   if ( PL_get_chars(ref, &s, CVT_ALL|CVT_WRITEQ|BUF_RING) )
733     return s;
734 
735   throw PlTypeError("text", ref);
736 }
737 
738 __inline PlTerm::operator wchar_t *(void) const
739 { wchar_t *s;
740 
741   if ( PL_get_wchars(ref, NULL, &s, CVT_ALL|CVT_WRITEQ|BUF_RING) )
742     return s;
743 
744   throw PlTypeError("text", ref);
745 }
746 
747 __inline PlTerm::operator long(void) const
748 { long v;
749 
750   if ( PL_get_long(ref, &v) )
751     return v;
752 
753   throw PlTypeError("integer", ref);
754 }
755 
756 __inline PlTerm::operator int(void) const
757 { int v;
758 
759   if ( PL_get_integer(ref, &v) )
760     return v;
761 
762   throw PlTypeError("integer", ref);
763 }
764 
765 __inline PlTerm::operator double(void) const
766 { double v;
767 
768   if ( PL_get_float(ref, &v) )
769     return v;
770 
771   throw PlTypeError("float", ref);
772 }
773 
PlAtom(void)774 __inline PlTerm::operator PlAtom(void) const
775 { atom_t v;
776 
777   if ( PL_get_atom(ref, &v) )
778     return PlAtom(v);
779 
780   throw PlTypeError("atom", ref);
781 }
782 
783 __inline PlTerm::operator void *(void) const
784 { void *ptr;
785 
786   if ( PL_get_pointer(ref, &ptr) )
787     return ptr;
788 
789   throw PlTypeError("pointer", ref);
790 }
791 
792 					/* compounds */
793 
794 __inline PlTerm
795 PlTerm::operator [](ARITY_T index) const
796 { PlTerm t;
797 
798   if ( PL_get_arg(index, ref, t.ref) )
799     return t;
800 
801   if ( !PL_is_compound(ref) )
802     throw PlTypeError("compound", ref);
803   else
804   { if ( !PL_put_integer(t.ref, index) )
805       throw PlResourceError();
806 
807     if ( index < 1 )
808       throw PlDomainError("not_less_than_zero", t.ref);
809     else
810       throw PlDomainError("arity", t.ref); /* TBD: proper exception */
811   }
812 }
813 
814 
815 __inline ARITY_T
arity()816 PlTerm::arity() const
817 { atom_t name;
818   ARITY_T arity;
819 
820   if ( PL_get_name_arity(ref, &name, &arity) )
821     return arity;
822 
823   throw PlTypeError("compound", ref);
824 }
825 
826 
827 __inline const char *
name()828 PlTerm::name() const
829 { atom_t name;
830   ARITY_T arity;
831 
832   if ( PL_get_name_arity(ref, &name, &arity) )
833     return PL_atom_chars(name);
834 
835   throw PlTypeError("compound", ref);
836 }
837 
838 
839 					/* Unification */
840 
841 __inline int PlTerm::operator =(const PlTerm &t2)	/* term = term */
842 { int rc = PL_unify(ref, t2.ref);
843   term_t ex;
844 
845   if ( !rc && (ex=PL_exception(0)) )
846     throw PlResourceError(ex);
847   return rc;
848 }
849 
850 __inline int PlTerm::operator =(const PlAtom &a)	/* term = atom */
851 { int rc = PL_unify_atom(ref, a.handle);
852   term_t ex;
853 
854   if ( !rc && (ex=PL_exception(0)) )
855     throw PlResourceError(ex);
856   return rc;
857 }
858 
859 __inline int PlTerm::operator =(const char *v)		/* term = atom */
860 { int rc = PL_unify_atom_chars(ref, v);
861   term_t ex;
862 
863   if ( !rc && (ex=PL_exception(0)) )
864     throw PlResourceError(ex);
865   return rc;
866 }
867 
868 __inline int PlTerm::operator =(const wchar_t *v)	/* term = atom */
869 { int rc = PL_unify_wchars(ref, PL_ATOM, (size_t)-1, v);
870   term_t ex;
871 
872   if ( !rc && (ex=PL_exception(0)) )
873     throw PlResourceError(ex);
874   return rc;
875 }
876 
877 __inline int PlTerm::operator =(long v)
878 { int rc = PL_unify_integer(ref, v);
879   term_t ex;
880 
881   if ( !rc && (ex=PL_exception(0)) )
882     throw PlResourceError(ex);
883   return rc;
884 }
885 
886 __inline int PlTerm::operator =(int v)
887 { int rc = PL_unify_integer(ref, v);
888   term_t ex;
889 
890   if ( !rc && (ex=PL_exception(0)) )
891     throw PlResourceError(ex);
892   return rc;
893 }
894 
895 __inline int PlTerm::operator =(double v)
896 { int rc = PL_unify_float(ref, v);
897   term_t ex;
898 
899   if ( !rc && (ex=PL_exception(0)) )
900     throw PlResourceError(ex);
901   return rc;
902 }
903 
904 __inline int PlTerm::operator =(const PlFunctor &f)
905 { int rc = PL_unify_functor(ref, f.functor);
906   term_t ex;
907 
908   if ( !rc && (ex=PL_exception(0)) )
909     throw PlResourceError(ex);
910   return rc;
911 }
912 
913 					/* comparison */
914 
915 
916 __inline int PlTerm::operator ==(long v) const
917 { long v0;
918 
919   if ( PL_get_long(ref, &v0) )
920     return v0 == v;
921 
922   throw PlTypeError("integer", ref);
923 }
924 
925 __inline int PlTerm::operator !=(long v) const
926 { long v0;
927 
928   if ( PL_get_long(ref, &v0) )
929     return v0 != v;
930 
931   throw PlTypeError("integer", ref);
932 }
933 
934 __inline int PlTerm::operator <(long v) const
935 { long v0;
936 
937   if ( PL_get_long(ref, &v0) )
938     return v0 < v;
939 
940   throw PlTypeError("integer", ref);
941 }
942 
943 __inline int PlTerm::operator >(long v) const
944 { long v0;
945 
946   if ( PL_get_long(ref, &v0) )
947     return v0 > v;
948 
949   throw PlTypeError("integer", ref);
950 }
951 
952 __inline int PlTerm::operator <=(long v) const
953 { long v0;
954 
955   if ( PL_get_long(ref, &v0) )
956     return v0 <= v;
957 
958   throw PlTypeError("integer", ref);
959 }
960 
961 __inline int PlTerm::operator >=(long v) const
962 { long v0;
963 
964   if ( PL_get_long(ref, &v0) )
965     return v0 >= v;
966 
967   throw PlTypeError("integer", ref);
968 }
969 
970 				      /* comparison (string) */
971 
972 __inline int PlTerm::operator ==(const char *s) const
973 { char *s0;
974 
975   if ( PL_get_chars(ref, &s0, CVT_ALL) )
976     return strcmp(s0, s) == 0;
977 
978   throw PlTypeError("text", ref);
979 }
980 
981 __inline int PlTerm::operator ==(const wchar_t *s) const
982 { wchar_t *s0;
983 
984   if ( PL_get_wchars(ref, NULL, &s0, CVT_ALL) )
985     return wcscmp(s0, s) == 0;
986 
987   throw PlTypeError("text", ref);
988 }
989 
990 __inline int PlTerm::operator ==(const PlAtom &a) const
991 { atom_t v;
992 
993   if ( PL_get_atom(ref, &v) )
994     return v == a.handle;
995 
996   throw PlTypeError("atom", ref);
997 }
998 
999 
1000 		 /*******************************
1001 		 *	   COMPOUND (BODY)	*
1002 		 *******************************/
1003 
1004 __inline void
PlPutTerm(term_t to,term_t from)1005 PlPutTerm(term_t to, term_t from)
1006 { if ( !PL_put_term(to, from) )
1007     throw PlResourceError();
1008 }
1009 
1010 
1011 __inline
PlCompound(const char * text)1012 PlCompound::PlCompound(const char *text) : PlTerm()
1013 { term_t t = PL_new_term_ref();
1014 
1015   if ( !PL_chars_to_term(text, t) )
1016     throw PlException(t);
1017 
1018   PlPutTerm(ref, t);
1019 }
1020 
1021 __inline
PlCompound(const wchar_t * text)1022 PlCompound::PlCompound(const wchar_t *text) : PlTerm()
1023 { term_t t = PL_new_term_ref();
1024 
1025   if ( !PL_wchars_to_term(text, t) )
1026     throw PlException(t);
1027 
1028   PlPutTerm(ref, t);
1029 }
1030 
1031 __inline
PlCompound(const char * functor,const PlTermv & args)1032 PlCompound::PlCompound(const char *functor, const PlTermv &args) : PlTerm()
1033 { if ( !PL_cons_functor_v(ref,
1034 			  PL_new_functor(PL_new_atom(functor), args.size),
1035 			  args.a0) )
1036     throw PlResourceError();
1037 }
1038 
1039 __inline
PlCompound(const wchar_t * functor,const PlTermv & args)1040 PlCompound::PlCompound(const wchar_t *functor, const PlTermv &args) : PlTerm()
1041 { if ( !PL_cons_functor_v(
1042 	    ref,
1043 	    PL_new_functor(PL_new_atom_wchars(wcslen(functor), functor),
1044 			   args.size),
1045 	    args.a0) )
1046     throw PlResourceError();
1047 }
1048 
1049 		 /*******************************
1050 		 *	   TERMV (BODY)		*
1051 		 *******************************/
1052 
1053 
PlTermv(PlTerm m0)1054 __inline PlTermv::PlTermv(PlTerm m0)
1055 { size = 1;
1056   a0 = m0.ref;
1057 }
1058 
PlTermv(PlTerm m0,PlTerm m1)1059 __inline PlTermv::PlTermv(PlTerm m0, PlTerm m1)
1060 { size = 2;
1061   if ( !(a0 = PL_new_term_refs(2)) )
1062     throw PlResourceError();
1063   PlPutTerm(a0+0, m0);
1064   PlPutTerm(a0+1, m1);
1065 }
1066 
PlTermv(PlTerm m0,PlTerm m1,PlTerm m2)1067 __inline PlTermv::PlTermv(PlTerm m0, PlTerm m1, PlTerm m2)
1068 { size = 3;
1069   if ( !(a0 = PL_new_term_refs(3)) )
1070     throw PlResourceError();
1071   PlPutTerm(a0+0, m0);
1072   PlPutTerm(a0+1, m1);
1073   PlPutTerm(a0+2, m2);
1074 }
1075 
PlTermv(PlTerm m0,PlTerm m1,PlTerm m2,PlTerm m3)1076 __inline PlTermv::PlTermv(PlTerm m0, PlTerm m1, PlTerm m2, PlTerm m3)
1077 { size = 4;
1078   if ( !(a0 = PL_new_term_refs(4)) )
1079     throw PlResourceError();
1080   PlPutTerm(a0+0, m0);
1081   PlPutTerm(a0+1, m1);
1082   PlPutTerm(a0+2, m2);
1083 
1084   PlPutTerm(a0+3, m3);
1085 }
1086 
PlTermv(PlTerm m0,PlTerm m1,PlTerm m2,PlTerm m3,PlTerm m4)1087 __inline PlTermv::PlTermv(PlTerm m0, PlTerm m1, PlTerm m2,
1088 			  PlTerm m3, PlTerm m4)
1089 { size = 5;
1090   if ( !(a0 = PL_new_term_refs(5)) )
1091     throw PlResourceError();
1092   PlPutTerm(a0+0, m0);
1093   PlPutTerm(a0+1, m1);
1094   PlPutTerm(a0+2, m2);
1095   PlPutTerm(a0+3, m3);
1096   PlPutTerm(a0+4, m4);
1097 }
1098 
1099 
1100 __inline PlTerm
1101 PlTermv::operator [](int n) const
1102 { if ( n < 0 || n >= size )
1103     throw PlTermvDomainError(size, n);
1104 
1105   return PlTerm(a0+n);
1106 }
1107 
1108 
1109 		 /*******************************
1110 		 *	EXCEPTIONS (BODY)       *
1111 		 *******************************/
1112 
1113 __inline PlException::operator const char *(void)
1114 { PlFrame fr;
1115 #ifdef USE_PRINT_MESSAGE
1116   PlTermv av(2);
1117 
1118   av[0] = PlCompound("print_message",
1119 		     PlTermv("error", ref));
1120   PlQuery q("$write_on_string", av);
1121   if ( q.next_solution() )
1122     return (char *)av[1];
1123 #else
1124   PlTermv av(2);
1125   av[0] = PlTerm(ref);
1126   PlQuery q("$messages", "message_to_string", av);
1127   if ( q.next_solution() )
1128     return (char *)av[1];
1129 #endif
1130   return "[ERROR: Failed to generate message.  Internal error]\n";
1131 }
1132 
1133 
1134 __inline PlException::operator const wchar_t *(void)
1135 { PlFrame fr;
1136 #ifdef USE_PRINT_MESSAGE
1137   PlTermv av(2);
1138 
1139   av[0] = PlCompound("print_message",
1140 		     PlTermv("error", ref));
1141   PlQuery q("$write_on_string", av);
1142   if ( q.next_solution() )
1143     return (wchar_t *)av[1];
1144 #else
1145   PlTermv av(2);
1146   av[0] = PlTerm(ref);
1147   PlQuery q("$messages", "message_to_string", av);
1148   if ( q.next_solution() )
1149     return (wchar_t *)av[1];
1150 #endif
1151   return L"[ERROR: Failed to generate message.  Internal error]\n";
1152 }
1153 
1154 
1155 __inline void
cppThrow()1156 PlException::cppThrow()
1157 { term_t a = PL_new_term_ref();
1158   atom_t name;
1159   ARITY_T arity;
1160 
1161   if ( PL_get_arg(1, ref, a) &&
1162        PL_get_name_arity(a, &name, &arity) )
1163   { const char *s = PL_atom_chars(name);
1164 
1165     if ( strcmp(s, "type_error") == 0 )
1166       throw PlTypeError(ref);
1167     if ( strcmp(s, "domain_error") == 0 )
1168       throw PlDomainError(ref);
1169     if ( strcmp(s, "resource_error") == 0 )
1170       throw PlResourceError(ref);
1171   }
1172 
1173   throw *this;
1174 }
1175 
1176 
1177 		 /*******************************
1178 		 *	    QUERY (BODY)	*
1179 		 *******************************/
1180 
1181 __inline int
next_solution()1182 PlQuery::next_solution()
1183 { int rval;
1184 
1185   if ( !(rval = PL_next_solution(qid)) )
1186   { term_t ex;
1187 
1188     PL_close_query(qid);
1189     qid = 0;
1190 
1191     if ( (ex = PL_exception(0)) )
1192       PlException(ex).cppThrow();
1193   }
1194   return rval;
1195 }
1196 
1197 
1198 		 /*******************************
1199 		 *	      ENGINE		*
1200 		 *******************************/
1201 
1202 class PlError
1203 {
1204 public:
1205   char *message;
1206 
PlError(const char * msg)1207   PlError(const char *msg)
1208   { size_t len = strlen(msg)+1;
1209     message = new char[len];
1210 #ifdef _MSC_VER				/* Yek */
1211 #pragma warning( push )
1212 #pragma warning (disable:4996)
1213 #endif
1214     strncpy(message, msg, len);
1215 #ifdef _MSC_VER
1216 #pragma warning( pop )
1217 #endif
1218   }
1219 
~PlError()1220   ~PlError()
1221   {
1222     delete[] message;
1223   }
1224 };
1225 
1226 
1227 class PlEngine
1228 {
1229 public:
1230 
PlEngine(int argc,char ** argv)1231   PlEngine(int argc, char **argv)
1232   { if ( !PL_initialise(argc, argv) )
1233       throw PlError("failed to initialise");
1234   }
1235 
PlEngine(char * av0)1236   PlEngine(char *av0)
1237   { int ac = 0;
1238     char **av = (char **)malloc(sizeof(char *) * 2);
1239 
1240     av[ac++] = av0;
1241 
1242     if ( !PL_initialise(1, av) )
1243       throw PlError("failed to initialise");
1244   }
1245 
~PlEngine()1246   ~PlEngine()
1247   { PL_cleanup(0);
1248   }
1249 };
1250 
1251 
1252 		 /*******************************
1253 		 *     REGISTER PREDICATES	*
1254 		 *******************************/
1255 
1256 #ifndef PROLOG_MODULE
1257 #define PROLOG_MODULE (const char*)NULL
1258 #endif
1259 
1260 #define NAMED_PREDICATE(plname, name, arity) \
1261 	static foreign_t \
1262 	pl_ ## name ## __ ## arity(PlTermv PL_av); \
1263 	static foreign_t \
1264 	_pl_ ## name ## __ ## arity(term_t t0, int a, control_t c) \
1265 	{ (void)a; (void)c; \
1266           try \
1267 	  { \
1268 	    return pl_ ## name ## __ ## arity(PlTermv(arity, t0)); \
1269 	  } catch ( PlException &ex ) \
1270 	  { return ex.plThrow(); \
1271 	  } \
1272 	} \
1273 	static PlRegister _x ## name ## __ ## arity(PROLOG_MODULE, plname, arity, \
1274 					    _pl_ ## name ## __ ## arity); \
1275 	static foreign_t pl_ ## name ## __ ## arity(PlTermv PL_av)
1276 
1277 #define NAMED_PREDICATE0(plname, name) \
1278 	static foreign_t \
1279 	pl_ ## name ## __0(void); \
1280 	static foreign_t \
1281 	_pl_ ## name ## __0(term_t t0, int a, control_t c) \
1282 	{ (void)t0; (void)a; (void)c; \
1283           try \
1284 	  { \
1285 	    return pl_ ## name ## __0(); \
1286 	  } catch ( PlException &ex ) \
1287 	  { return ex.plThrow(); \
1288 	  } \
1289 	} \
1290 	static PlRegister _x ## name ## __0(PROLOG_MODULE, plname, 0, \
1291 					    _pl_ ## name ## __0); \
1292 	static foreign_t pl_ ## name ## __0(void)
1293 
1294 #define NAMED_PREDICATE_NONDET(plname, name, arity)          \
1295 	static foreign_t \
1296 	pl_ ## name ## __ ## arity(PlTermv PL_av, control_t handle);       \
1297 	static foreign_t \
1298 	_pl_ ## name ## __ ## arity(term_t t0, int a, control_t c) \
1299 	{ (void)a; \
1300           try \
1301 	  { \
1302 	    return pl_ ## name ## __ ## arity(PlTermv(arity, t0), c); \
1303 	  } catch ( PlException &ex ) \
1304 	  { return ex.plThrow(); \
1305 	  } \
1306 	} \
1307         static PlRegister _x ## name ## __ ## arity(PROLOG_MODULE, plname, arity, \
1308                                                     _pl_ ## name ## __ ## arity, \
1309                                                     PL_FA_NONDETERMINISTIC | PL_FA_VARARGS); \
1310 	static foreign_t pl_ ## name ## __ ## arity(PlTermv PL_av, control_t handle)
1311 
1312 #define PREDICATE0(name)              NAMED_PREDICATE0(#name, name)
1313 #define PREDICATE(name, arity)        NAMED_PREDICATE(#name, name, arity)
1314 #define PREDICATE_NONDET(name, arity) NAMED_PREDICATE_NONDET(#name, name, arity)
1315 
1316 #define PL_A1  PL_av[0]
1317 #define PL_A2  PL_av[1]
1318 #define PL_A3  PL_av[2]
1319 #define PL_A4  PL_av[3]
1320 #define PL_A5  PL_av[4]
1321 #define PL_A6  PL_av[5]
1322 #define PL_A7  PL_av[6]
1323 #define PL_A8  PL_av[7]
1324 #define PL_A9  PL_av[8]
1325 #define PL_A10 PL_av[9]
1326 
1327 #ifndef PL_SAFE_ARG_MACROS
1328 #define A1	PL_A1
1329 #define A2	PL_A2
1330 #define A3	PL_A3
1331 #define A4	PL_A4
1332 #define A5	PL_A5
1333 #define A6	PL_A6
1334 #define A7	PL_A7
1335 #define A8	PL_A8
1336 #define A9	PL_A9
1337 #define A10	PL_A10
1338 #endif
1339 
1340 #endif /*_SWI_CPP_H*/
1341