SWICLI - Help Needed TAKEOVER Maintainers and Improvers

110 views
Skip to first unread message

Douglas Miles

unread,
Jan 6, 2016, 7:48:35 AM1/6/16
to swi-p...@googlegroups.com
A few years ago I created a system to allow Prolog developers the ability to use already compiled C code fro SWI.   Sort of like the foreign interface but with the difference is no compiler was required.  The closest analogy analogy was CFFI for lisp.  In fact I ended up deciding it was simpler to just read their .cffi files for the meta info and use that for structure/pointer alignment instead of designing a whole new system in P-Expressions. (after all we even have a https://github.com/logicmoo/swicli/blob/master/cffi-tests/swi-prolog.cffi)
Also created the ability that from Prolog you could generate callbacks ad structs to be used by C programs (So a Two-way C interface) without ever getting your hands dirty in actual C code and compilers (I cheat using the  Application Binary Interface (ABI) of .NET/MONO who needed a  FFI ) and then wrote some runtime type compilers to use that ABI for prolog (in C#))


   It works on Windows and linux both.

Here is an example:
?- use_module(library(swicffi)).
Cannot install hook ThreadExit to Mono
Swicli.Library.Embedded.install suceeded
true.
?- cli_get_dll('libc.so.6',DLL),cli_call(DLL,printf,["I have been clicked %d times\n", 2],O).
I have been clicked 2 times
DLL = @'C#666',
O = @void.


The problem now: as useful as it is I dont have the time to make it really easy to use and haven't written any explanations or examples for using the Native Libraries above!  


It disappoints me greatly I dont have the time to maintain it.   So looking for volunteers who wish to basically take it over and turn it into what it should be!


https://github.com/logicmoo/swicli
















 It has several capabilities and looks and feels a bit like JPL .. in fact.. 
It only has a couple few help pages that mostly explain how to use external "Managed NET/Mono"  code.. like:


PublicShow sourceswicli.pl -- SWI-Prolog 2-Way interface to .NET/Mono

Introduction

This is an overview of an interface which allows SWI-Prolog programs to dynamically create and manipulate .NET objects.

Here are some significant features of the interface and its implementation:

  • API is similar to that of XPCE: the four main interface calls are cli_new, cli_call, cli_set and cli_get (there is a single cli_free, though .NET's garbage collection is extended transparently into Prolog)
  • Uses @/1 to construct representations of certain .NET values; if @/1 is defined as a prefix operator (as used by XPCE), then you can write @false, @true, @null etc. in your source code; otherwise (and for portability) you'll have to write e.g. @(true) etc.
  • cli_call/4 (modeled from JPL's jpl_call/4) resolves overloaded methods automatically and dynamically, inferring the types of the call's actual parameters, and identifying the most specific of the applicable method implementations (similarly, cli_new resolves overloaded constructors)
  • Completely dynamic: no precompilation is required to manipulate any .NET classes which can be found at run time, and any objects which can be instantiated from them
  • Interoperable with SwiPlCS's .NET API (which has evolved from Uwe Lesta's SwiPlCS)
  • Exploits the Invocation API of the .NET P/Invoke Interface: this is a mandatory feature of any compliant .NET
  • Implemented with a fair amount of C# code and Prolog code in one module (swicli.pl) (which I believe to be ISO Standard Prolog compliant and portable) and a SWI-Prolog-specific foreign library (swicli[32].dll for Windows and swicli[32].so *nix), implemented in ANSI C but making a lot of use of the SWI-Prolog Foreign Language Interface Then uses Swicli.Library.dll (Managed binary) that runs on both Mono and .NET runtimes.
  • the Prolog-calls-CLI (mine) and CLI-calls-Prolog (Ewe's) parts of SWICLI are largely independent; mine concentrates on representing all .NET data values and objects within Prolog, and supporting manipulation of objects; Ewe's concentrates on representing any Prolog term within .NET, and supporting the calling of goals within Prolog and the retrieving of results back into .NET
  • @(terms) are canonical (two references are ==/2 equal if-and-only-if they refer to the same object within the .NET)
  • are represented as structures containing a distinctive atom so as to exploit SWI-Prolog's atom garbage collection: when an object reference is garbage-collected in Prolog, the .NET garbage collector is informed, so there is sound and complete overall garbage collection of .NET objects within the combined Prolog+.NET system
  • .NET class methods can be called by name: SWICLI invisibly fetches (and caches) essential details of method invocation, exploiting .NET Reflection facilities
  • Reason about the types of .NET data values, object references, fields and methods: SWICLI supports a canonical representation of all .NET types as structured terms (e.g. array(array(byte))) and also as atomic .NET signatures
  • when called from Prolog, void methods return a @(void) value (which is distinct from all other SWICLI values and references)
  • Tested on Windows XP, Windows7 and Fedora Linux, but is believed to be readily portable to SWI-Prolog on other platforms as far as is feasible, .NET data values and object references are represented within Prolog canonically and without loss of information (minor exceptions: .NET float and double values are both converted to Prolog float values; .NET byte, char, short, int and long values are all converted to Prolog integer values; the type distinctions which are lost are normally of no significance)
  • Requires .NET 2.0 and class libraries (although it doesn't depend on any .NET 2-specific facilities, and originally was developed for use with both 1.0 thru 4.0 .NETs, I haven't tested it with 1.0 recently, and don't support this)
    ?- use_module(library(swicli)).
    
    ?- cli_call('System.Threading.ThreadPool','GetAvailableThreads'(X,Y),_).
    
    X=499, Y=1000
    
    

    ?- cli_call('System.Environment','Version',X),cli_writeln(X). "2.0.50727.5448" X = @'C#499252128'.

    ==

    Doc root and Download will be findable from http://code.google.com/p/opensim4opencog/wiki/SwiCLI

    @see CSharp.txt

author
- Douglas Miles
cli_load_lib(+AppDomainName, +AssemblyPartialName, +FullClassName, +StaticMethodName)
Loads an assembly into AppDomainName

cli_load_lib/4 is what was used to bootstrap SWICLI (it defined the next stage where cli_load_assembly/1) became present

remember to: export LD_LIBRARY_PATH=/development/opensim4opencog/bin:$LD_LIBRARY_PATH

in swicli.pl we called:

:- cli_load_lib('SWIProlog','Swicli.Library','Swicli.Library.Embedded','install').
cli_lib_type(-LibTypeName)
LibTypeName is an atom that denotes the implementation class SWICLI uses
cli_load_assembly(+AssemblyPartialNameOrPath)
cli_load_assembly_uncaught(+AssemblyPartialNameOrPath)
the cli_<Predicates> came because we had:
?- cli_load_assembly('Swicli.Library').

The uncaught version allows exception to come from .NET

cli_load_assembly_methods(+AssemblyPartialNameOrPath, +OnlyPrologVisible, +StringPrefixOrNull)
Loads foriegn predicates from Assembly
?- cli_load_assembly_methods('Swicli.Library', @false, "cli_").
cli_add_foreign_methods(+Type, +OnlyPrologVisible, +StringPrefixOrNull)
Loads foriegn predicates from Type
cli_add_assembly_search_path(+Path)
cli_remove_assembly_search_path(+Path)
Add or remove directories to the search path
?- cli_add_assembly_search_path('c:/myproj/bin').

?- cli_remove_assembly_search_path('c:/myproj/bin').

This now makes the System assembly resolver see Assemblies in that directory

Simular to Windows: adding to %PATH% Linux: adding to $MONO_PATH

cli_non_obj(+Obj)
is null or void or var
cli_non_null(+Obj)
is not null or void
cli_is_null(+Obj)
equiv to Obj == @(null)
cli_null(+Obj)
construct a null
cli_is_true(+Obj)
equiv to Obj == @(true)
cli_true(+Obj)
construct a @(true)
cli_is_false(+Obj)
equiv to Obj == @(false)
cli_false(+Obj)
construct a @(false)
cli_is_void(+Obj)
equiv to Obj == @(void)
cli_void(+Obj)
construct a @(void)
cli_is_type(+Obj)
equiv to cli_is_type(Obj,'System.Type')
cli_is_object(+Obj)
is Object a CLR object and not null or void (includes struct,enum,object,event)
cli_is_tagged_object(+Obj)
is Object a ref object (maybe null or void) (excludes struct,enum,object/N,event refernces)
cli_is_ref(+Obj)
is Object a ref object and not null or void (excludes struct,enum,object/N,event refernces)
cli_member_doc(+Memb, +Doc, +Xml)
cli_members(+ClazzOrInstance, -Members)
cli_memb(O, X)
cli_memb(O, F, X)
cli_memb(O,X):-cli_members(O,Y),member(X,Y).
cli_memb(O,F,X):-cli_memb(O,X),member(F,[f,p, c,m ,e]),functor(X,F,_).

Object to the member infos of it

   3 ?- cli_new('System.Collections.Generic.List'(string),[int],[10],O),cli_members(O,M),!,member(E,M),writeq(E),nl,fail.
   f(0,'_items'(arrayOf('String')))
   f(1,'_size'('Int32'))
   f(2,'_version'('Int32'))
   f(3,'_syncRoot'('Object'))
   f(4,'_emptyArray'(arrayOf('String')))
   f(5,'_defaultCapacity'('Int32'))
   p(0,'Capacity'('Int32'))
   p(1,'Count'('Int32'))
   p(2,'System.Collections.IList.IsFixedSize'('Boolean'))
  
cli_is_type(+Impl, ?Type)
tests to see if the Impl Object is assignable to Type
cli_subclass(+Subclass, +Superclass)
tests to see if the Subclass is assignable to Superclass
cli_get_typespec(+Obj, ?TypeSpec)
gets or checks the TypeSpec
cli_get_typeref(+Obj, ?TypeRef)
gets or checks the TypeRef
cli_get_typename(+Obj, ?TypeName)
gets or checks the TypeName
cli_type_to_typespec(+ClazzSpec, -Value)
coerces a ClazzSpec to a Value representing a TypeSpec term
cli_add_tag(+RefObj, +TagString)
lowlevel access to create a tag name
?- cli_new(array(string),[int],[32],O),cli_add_tag(O,'string32').

?- cli_get_type(@(string32),T),cli_writeln(T).

cli_remove_tag(+TagString)
lowlevel access to remove a tag name
cli_to_ref(+Obj, +Ref)
return a @(Ref) version of the object (even if a enum)
15 ?- cli_to_ref(sbyte(127),O),cli_get_type(O,T),cli_writeln(O is T).
"127"is"System.SByte"
O = @'C#283319280',
T = @'C#283324332'.

16 ?- cli_to_ref(long(127),O),cli_get_type(O,T),cli_writeln(O is T).
"127"is"System.Int64"
O = @'C#283345876',
T = @'C#283345868'.

17 ?- cli_to_ref(ulong(127),O),cli_get_type(O,T),cli_writeln(O is T).
"127"is"System.UInt64"
O = @'C#283346772',
T = @'C#283346760'.

15 ?- cli_to_ref(sbyte(127),O),cli_get_type(O,T),cli_writeln(O is T).
"127"is"System.SByte"
O = @'C#283319280',
T = @'C#283324332'.

16 ?- cli_to_ref(long(127),O),cli_get_type(O,T),cli_writeln(O is T).
"127"is"System.Int64"
O = @'C#283345876',
T = @'C#283345868'.

18 ?- cli_to_ref(343434127,O),cli_get_type(O,T),cli_writeln(O is T).
"343434127"is"System.Int32"
O = @'C#281925284',
T = @'C#281925280'.

19 ?- cli_to_ref(3434341271,O),cli_get_type(O,T),cli_writeln(O is T).
"3434341271"is"System.UInt64"
O = @'C#281926616',
T = @'C#283346760'.

21 ?- cli_to_ref(343434127111,O),cli_get_type(O,T),cli_writeln(O is T).
"343434127111"is"System.UInt64"
O = @'C#281930092',
T = @'C#283346760'.

28 ?- cli_to_ref(34343412711111111111111111111111111111,O),cli_get_type(O,T),cli_writeln(O is T).
"34343412711111111111111111111111111111"is"java.math.BigInteger"
O = @'C#281813796',
T = @'C#281810860'.
cli_to_immediate(+Ref, -Immediate)
return an Immediate value of Ref to just REf if no immediate type exists
cli_cast(+Value, +ClazzSpec, -Ref)
cli_cast_immediate(+Value, +ClazzSpec, -Immediate)
Convert the type of Value to ClazzSpec returning either a Ref or Immediate value.
?- cli_cast(1,'double',X).
X = @'C#568261440'.

?- cli_cast(1,'System.DayOfWeek',X).
X = @'C#568269000'.

?- cli_cast_immediate(1,'System.DayOfWeek',X).
X = enum('DayOfWeek', 'Monday').

?- cli_cast_immediate(1.0,'System.DayOfWeek',X).
X = enum('DayOfWeek', 'Monday').

?- cli_cast_immediate(1.01,'System.DayOfWeek',X).
ERROR: Having time of it convcerting 1.01 to System.DayOfWeek why System.ArgumentException: Requested value '1.01' was not found.
cli_tracker_begin(-Tracker)
Return a Tracker ref and all objects created from this point can be released via cli_tracker_free/1
cli_tracker_free(+Tracker)
See also
cli_tracker_begin/1
cli_free(+RefObject)
remove a RefObject from the heap
cli_heap(+RefObject)
Pin a RefObject onto the heap
cli_with_gc(+Call)
as ref objects are created they are tracked .. when the call is complete any new object tags are released uses Forienly defined cli_tracker_begin/1 and cli_tracker_free/1
cli_with_lock(+Lock, +Call)
Lock the first arg while calling Call
cli_lock_enter(+LockObj)
Does a Monitor.Enter on LockObj
cli_lock_exit(+LockObj)
Does a Monitor.Exit on LockObj
cli_write(+Obj)
writes an object out
cli_writeln(+Obj)
writes an object out with a new line
cli_fmt(+String, +Args)
cli_fmt(+Obj, +String, +Args)
use .NET system string.Format(String,ArgsObj is WriteLineDelegate
to_string(+Obj, -String)
cli_to_str(+Obj, -String)
Resolves inner @(Obj)s to strings
cli_to_str_raw(+Obj, -String)
cli_java_to_string(+Obj, -Value)
Resolves @(Obj) to string
cli_halt
cli_halt(+Obj)
cli_throw(+Ex)
throw an exception to .NET
cli_break(+Ex)
cli_debug(+Obj)
cli_debug(+Fmt, Args)
writes to user_error
cli_col(+Col, -Elem)
cli_enumerator_element(+Enumer, -Elem)
cli_iterator_element(+Iter, -Elem)
Iterates out Elem for Col/Iter/Enumer
   ?- cli_new('System.Collections.Generic.List'('System.String'),[int],[10],Obj).
   Obj = @'C#516939544'.


   ?- cli_get($Obj,'Count',Out).
   Out = 0.


   ?- cli_call($Obj,'Add'("foo"),Out).
   Out = @void.


   ?- cli_call($Obj,'Add'("bar"),Out).
   Out = @void.


   ?- cli_get($Out,'Count',Out).
   Out = 2.


   ?- cli_col($Obj,E).
   E = "foo" ;
   E = "bar" ;
   false.
cli_col_add(+Col, +Item)
add an Item to Col
cli_col_contains(+Col, +Item)
Test an Item in Col
cli_col_remove(+Col, +Item)
Remove an Item in Col
cli_col_removeall(+Col)
Clears a Col
cli_col_size(+Col, ?Count)
Returns the Count
cli_set_element(+Obj, +IndexParams, +Item)
cli_add_element(+Obj, +Item)
todo
cli_make_list(+Obj, +Arg2, +Arg3)
See also
cli_new_list_1/2
cli_new_list_1(+Obj, +Arg2, +Arg3)
See also
cli_make_list/2
cli_sublist(+Mask, +List)
Test to see if Mask appears in List
cli_new_array(+ClazzSpec, +Rank, -Value)
cli_array_fill(+Obj, Arg2)
cli_array_fill_values(+Obj, Arg2)
cli_array_to_length(+Obj, Arg2)
cli_array_to_list(+Obj, +Arg2)
cli_array_to_term(+ArrayValue, -Value)
cli_array_to_termlist(+ArrayValue, -Value)
cli_term_to_array(+ArrayValue, -Value)
cli_array_to_term_args(+Array, -Term)
todo
cli_map(Map, ?Key, ?Value)
cli_map_add(+Map, +Key, +Value)
cli_map_set(+Map, +Key, +Value)
cli_map_remove(+Map, +Key)
cli_map_remove(+Map, ?Key, ?Value)
cli_map_removeall(+Map)
cli_map_size(+Map, -Count)
Map calls
cli_preserve(TF, :Call)
make Call with PreserveObjectType set to TF
member_elipse(Ele, Elipse)
?- member_elipse(E,{a,b,c}).
E = a ;
E = b ;
E = c.
cli_to_data(+Ref, -Term)
cli_to_data(+ValueCol, +Ref, -Term)
cli_getterm(+ValueCol, +Ref, -Term)
converts a Ref to prolog Term ValCol is a .NET List used to break cyclic loops
?- cli_cast("Yellow",'System.Drawing.Color',C),cli_to_data(C,D),writeq(D).
["R"=255,"G"=255,"B"=0,"A"=255,"IsKnownColor"= @true,"IsEmpty"= @false,"IsNamedColor"= @true,"IsSystemColor"= @false,"Name"="Yellow"]
C = @'C#802963000',
D = ["R"=255, "G"=255, "B"=0, "A"=255, "IsKnownColor"= @true, "IsEmpty"= @false, "IsNamedColor"= @true, "IsSystemColor"= @ ..., ... = ...].
cli_unify(OE, PE)
cli_make_default(+ClazzSpec, -Result)
cli_new(+ClassNameWithParams, -Result)
cli_new(+ClazzSpec, +Params, -Result)
cli_new(+ClazzSpec, +MemberSpec, +Params, -Result)
?- cli_load_assembly('IKVM.OpenJDK.Core')
?- cli_new('java.lang.Long'(long),[44],Out),cli_to_str(Out,Str).

same as..

?- cli_new('java.lang.Long',[long],[44],Out),cli_to_str(Out,Str).

arity 4 exists to specify generic types

?- cli_new('System.Int64',[int],[44],Out),cli_to_str(Out,Str).
?- cli_new('System.Text.StringBuilder',[string],["hi there"],Out),cli_to_str(Out,Str).
?- cli_new('System.Int32'(int),[44],Out),cli_to_str(Out,Str).

ClazzSpec can be:

  • an atomic classname e.g. 'java.lang.String'
  • an atomic descriptor e.g. '[I' or 'Ljava.lang.String;'
  • a suitable type i.e. any class(_,_) or array(_)

if ClazzSpec is an object (non-array) type or descriptor and Params is a list of values or references, then Result is the result of an invocation of that type's most specifically-typed constructor to whose respective formal parameters the actual Params are assignable (and assigned)

if ClazzSpec is an array type or descriptor and Params is a list of values or references, each of which is (independently) assignable to the array element type, then Result is a new array of as many elements as Params has members, initialised with the respective members of Params;

if ClazzSpec is an array type or descriptor and Params is a non-negative integer N, then Result is a new array of that type, with N elements, each initialised to CLR's appropriate default value for the type;

If Result is {Term} then we attempt to convert a new PlTerm instance to a corresponding term; this is of little obvious use here, but is consistent with cli_call/4 and cli_get/3

Make a "new string[32]" and get it's length.

 ?- cli_new(array(string),[int],[32],O),cli_get(O,'Length',L).
cli_call(+ClazzOrInstance, +CallTerm, -Result)
cli_call(+ClazzOrInstance, +MethodSpec, +Params, -Result)
cli_call_raw(+ClazzOrInstance, +MethodSpec, +Params, -Result)
cli_raise_event_handler(+ClazzOrInstance, +MemberSpec, +Params, -Result)
ClazzOrInstance should be:
  • an object reference (for static or instance methods)
  • a classname, descriptor or type (for static methods of the denoted class)

MethodSpec should be:

  • a method name (as an atom) (may involve dynamic overload resolution based on inferred types of params)

Params should be:

  • a proper list (perhaps empty) of suitable actual parameters for the named method

CallTerm should be:

  • a method name with parameters (may involve dynamic overload resolution based on inferred types of params)

finally, an attempt will be made to unify Result with the returned result

cli_lib_call(+CallTerm, -Result)
CallTerm should be:
  • a method name with parameters (may involve dynamic overload resolution based on inferred types of params)

finally, an attempt will be made to unify Result with the returned result

cli_set(+Obj, +NameValueParis:list)
cli_get(+Obj, +NameValueParis:list)
gets or set multiple values
cli_get(+ClazzOrInstance, +MemberSpec, -Value)
cli_set(+ClazzOrInstance, +MemberSpec, +Value)
cli_get_raw(+ClazzOrInstance, +MemberSpec, -Value)
cli_set_raw(+ClazzOrInstance, +MemberSpec, +Value)
cli_get_field(+ClazzOrInstance, +MemberSpec, -Value)
cli_set_field(+ClazzOrInstance, +MemberSpec, +Value)
cli_set_property(+ClazzOrInstance, +MemberSpec, +IndexValues, +Value)
cli_get_property(+ClazzOrInstance, +MemberSpec, +IndexValues, -Value)
_get/_set (the first two) Attempts to find the "best" member
  • Public properties, fields and bean-ifications (happy, is_happy, GetHappy, get_Happy, etc)
  • Nonpublic properties, fields and bean-ifications (is_happy, GetHappy, get_Happy, etc)
  • Case insensitive public and non-public

_raw is the foreign impls of the first two (Actually the above search impl is done from this _raw) _field will only try to set fields _property will only try to set fields

ClazzOrInstance can be:

  • a classname, a descriptor, or an (object or array) type (for static fields);
  • a non-array object (for static and non-static fields)
  • an array (for 'length' pseudo field, or indexed element retrieval), but not:
  • a String (clashes with class name; anyway, String has no fields to retrieve)

MemberSpec can be:

  • an atomic field name,
  • or an integral array index (to get an element from an array,
  • or a pair I-J of integers (to get a subrange (slice?) of an array)
  • A list of [a,b(1),c] to denoate cli getting X.a.b(1).c
  • [#f(fieldname),#p(propertyname),#p(propertyname,indexer)] when you want to avoid the search

IndexValues can be:

  • Property index params ["foo",1] or []

Value:

  • Getting, an attempt will be made to unify Value with the retrieved value
  • Setting, put Value
cli_new_event_waiter(+ClazzOrInstance, +MemberSpec, -WaitOn)
Creates a new ManualResetEvent (WaitOn) that when an Event is called WaitOn in pulsed so that cli_block_until_event/3 will unblock
cli_add_event_waiter(+WaitOn, +ClazzOrInstance, +MemberSpec, -NewWaitOn)
Adds a new Event to the ManualResetEvent (WaitOn) created by cli_new_event_waiter/3
cli_block_until_event(+WaitOn, +Time, +Lambda)
Calls (foriegnly defined) cli_block_until_event/4 and then cleansup the .NET objects.
cli_block_until_event(+WaitOn, +MaxTime, +TestVarsCode, -ExitCode)
foriegnly defined tododocs
cli_new_delegate(+DelegateClass, +PrologPred, -Value)
cli_new_delegate_term(+TypeFi, +PrologPred, +BooleanSaveKey, -Delegate)
todo
cli_add_event_handler(+Term1, +Arity, +IntPtrControl, Pred)
See also
cli_add_event_handler/4
cli_add_event_handler(+ClazzOrInstance, +MemberSpec, +PrologPred)
Create a .NET Delegate that calls PrologPred when MemberSpec is called
cli_remove_event_handler(+ClazzOrInstance, +MemberSpec, +PrologPred)
cli_new_prolog_collection(+PredImpl, +ElementType, -PBD)
Prolog Backed Collection
cli_new_prolog_dictionary(+PredImpl, +KeyType, +ValueType, -PBD)
Prolog Backed Dictionaries
module_functor(+Obj, Arg2, Arg3, Arg4)
cli_hide(+Pred)
hide Pred from tracing
cli_notrace(+Call) is nondet
use call/1 with trace turned off
cli_class_from_type(+Value, -Value)
cli_find_class(+ClazzName, -ClazzObject)
cli_find_type(+ClazzSpec, +ClassRef)
cli_get_class(+Value, -Value)
cli_get_classname(+Value, -Value)
cli_get_type(+Value, -Value)
cli_type_to_fullname(+Value, -Value)
cli_type_from_class(+Value, -Value)
todo
cli_is_layout(+MemberSpec)
cli_add_layout(+ClazzSpec, +MemberSpec)
cli_add_layout(+ClazzSpec, +MemberSpec, +ToSpec)
cli_add_recomposer(+ClazzSpec, +MemberSpec, +Obj2r, +R2obj)
need doc!
cli_find_constructor(+ClazzSpec, +MemberSpec, -Method)
cli_find_method(+ClazzOrInstance, +MemberSpec, -Method)
cli_add_shorttype(+Short, +Long)
cli_props_for_type(+ClazzSpec, +MemberSpecs)
need doc
cli_special_unify(+Obj, Arg2)
cli_expand(+Obj, Arg2)
cli_expanded(+Obj, Arg2)
cli_eval(+Obj, Arg2, Arg3)
cli_eval_hook(+Obj, Arg2, Arg3)
cli_set_hook(+Obj, Arg2, Arg3)
cli_get_hook(+Obj, Arg2, Arg3)
cli_subproperty(+Obj, Arg2)
cli_link_swiplcs(+Obj)
cli_demo(+Obj, Arg2)
cli_is_defined(+Obj, Arg2)
cli_interned(+Obj, Arg2, Arg3)
cli_intern(+Obj, Arg2, Arg3)
cli_get_symbol(+Obj, Arg2, Arg3)
need docs!

 

SWICLI 1.x Prolog API overview



Introduction

This is an overview of an interface which allows SWI-Prolog programs to dynamically create and manipulate .NET objects.

Here are some significant features of the interface and its implementation:

  • it is completely dynamic: no precompilation is required to manipulate any .NET classes which can be found at run time, and any objects which can be instantiated from them
  • it is interoperable with SWICLI's .NET API (which has evolved from Uwe Lesta's SwiPlCS)
  • it requires .NET 2.0 and class libraries (although it doesn't depend on any .NET 2-specific facilities, and originally was developed for use with both 1.0 thru 4.0 .NETs, I haven't tested it with 1.0 recently, and don't support this)
  • it exploits the Invocation API of the .NET P/Invoke Interface: this is a mandatory feature of any compliant .NET
  • it is implemented with a fair amount of C# code and Prolog code in one module (swicli.pl)  (which I believe to be ISO Standard Prolog compliant and portable) and a SWI-Prolog-specific foreign library (swicli[32].dll for Windows and swicli[32].so *nix), implemented in ANSI C but making a lot of use of the SWI-Prolog Foreign Language Interface Then uses Swicli.Library.dll (Managed binary) that runs on both Mono and .NET runtimes.
  • the foreign-language part has so far been tested on Windows XP, Windows7 and Fedora Linux, but is believed to be readily portable to SWI-Prolog on other platforms
  • as far as is feasible, .NET data values and object references are represented within Prolog canonically and without loss of information (minor exceptions: .NET float and double values are both converted to Prolog float values; .NET bytecharshortint and long values are all converted to Prolog integer values; the type distinctions which are lost are normally of no significance)
  • references within Prolog to .NET objects:
    • should be treated as opaque handles
    • are canonical (two references are ==/2 equal if-and-only-if they refer to the same object within the .NET)
    • are represented as structures containing a distinctive atom so as to exploit SWI-Prolog's atom garbage collection: when an object reference is garbage-collected in Prolog, the .NET garbage collector is informed, so there is sound and complete overall garbage collection of .NET objects within the combined Prolog+.NET system
  • .NET class methods can be called by name: SWICLI invisibly fetches (and caches) essential details of method invocation, exploiting .NET Reflection facilities
  • the API is similar to that of XPCE: the four main interface calls are cli_newcli_call, cli_set and cli_get (there is a single cli_free, though .NET's garbage collection is extended transparently into Prolog)
  • cli_call resolves overloaded methods automatically and dynamically, inferring the types of the call's actual parameters, and identifying the most specific of the applicable method implementations (similarly, cli_new resolves overloaded constructors)
  • Prolog code which uses the API calls is responsible for passing suitably-typed values and references, since the P/INVOKE doesn't perform complete dynamic type-checking, and nor currently does SWICLI (although theoverloaded method resolution mechanism could probably be adapted to do this)
  • Prolog code can reason about the types of .NET data values, object references, fields and methods: SWICLI supports a canonical representation of all .NET types as structured terms (e.g. array(array(byte))) and also as atomic .NET signatures
  • the Prolog-calls-.NET (mine) and .NET-calls-Prolog (Uwe Lesta's) parts of SWICLI are largely independent; mine concentrates on representing all .NET data values and objects within Prolog, and supporting manipulation of objects; Uwe Lesta concentrates on representing any Prolog term within .NET, and supporting the calling of goals within Prolog and the retrieving of results back into .NET
  • when called from Prolog, void methods return a void value (which is distinct from all other SWICLI values and references)
  • it uses @/1 to construct representations of certain .NET values; if  @/1 is defined as a prefix operator (as used by XPCE), then you can write @false@true@null etc. in your source code; otherwise (and for portability) you'll have to write e.g. @(true) etc.

SWICLI types (.NET types, as seen by Prolog)

All .NET values and object references which are passed between Prolog engines and .NET VMs via SWICLI's Prolog API are seen as instances of types within this simplified SWICLI type system:

datum   (this term is introduced, out of necessity, to refer jointly to values and refs)

is a value    (values are copied between Prolog and the .NET)

is a boolean

or a char

or a longintshort or byte

or a double or float

or a string   (an instance of System.String)

or a void     (an artificial value returned by calls to .NET void methods)

or a ref

is null

or an object    (held within the .NET, and represented in Prolog by a canonical reference)

is an array

or a class instance (other than of System.String)


representation of .NET values and references within Prolog

Instances of SWICLI types are represented within Prolog as follows:

boolean has two values, represented by @(true) and @(false)

char values are represented by corresponding Prolog integers

intshort and byte values are represented by corresponding Prolog integers

long values are represented as Prolog integers if possible (32-bit in current SWI-Prolog), else as jlong(Hi,Lo) where Hi is an integer corresponding to the top32 bits of the long, and Lo similarly represents the lower 32 bits

double and float values are represented as Prolog floats (which are equivalent to .NET doubles) (there may be minor rounding, normalisation or loss-of-precision issues when a .NET float is widened to a Prolog float then narrowed back again, but what the heck)

string values (immutable instances of System.String) are represented as Prolog atoms (in UTF-8 encoding)

null has only one value, represented as @(null)

void has only one value, represented as @(void)

array and class instance references are currently represented as @(Tag), where Tag ia an atom whose name encodes a P/INVOKE global reference value; this may change, but won't affect Prolog programs which respect the opacity of references


Representation of .NET types within Prolog (1): structured notation

The SWICLI Prolog API allows Prolog applications to inspect, manipulate, and reason about the types of .NET values, references, methods etc., and this section describes how these types themselves (as opposed to instances thereof) are represented.  Predicates which pass these type representations include cli_type_to_type/2cli_typename_to_type/2cli_datum_to_type/2cli_is_object_type/1cli_is_type/1cli_object_to_type/2,cli_primitive_type/1cli_ref_to_type/2cli_type_to_type/2cli_type_to_typename/2.

void is represented as void

null is represented as null

the primitive types are represented as booleancharbyteshortintlongfloatdouble

classes are represented as class(package_parts,classname_parts)

e.g.  class(['System','Forms'],['TextBox'])

array types are represented as array(type)

e.g.  array(boolean)

e.g.  array(class([System],['String'])

This structured notation for .NET types is designed to be convenient for composition and decomposition by matching (unification).


representation of .NET types within Prolog (2): descriptor notation

The descriptor notation for .NET types is one of two textual notations employed by the .NET and the .NET class libraries; SWICLI (necessarily) supports both (and supports conversion between all three representations).

Examples:

'bool' denotes boolean

'byte(4)' denotes System.Byte

'char' denotes System.Character

'short' denotes short

'int' denotes int32

'long' denotes long

'single' denotes float

'double' denotes double

'System.DateTime' (for example) denotes the System.Datetime

'type[]' denotes an array of type

'(argument_types)return_type' denotes the type of a method


representation of .NET types within Prolog (3): classname notation

The classname notation for .NET types is the other textual notation employed by the .NET and the .NET class libraries.  It is a (seemingly unnecessary) variation on the descriptor notation, used by a few P/INVOKE routines.  It has the slight advantage that, in the case of simple class types only, it resembles the .NET source text notation for classes.  This representation is supported only because certain P/INVOKE functions use it; it is used within SWICLI's implementation of cli_call/4 etc.  You may encounter this notation when tracing SWICLI activity, but otherwise you need not know about it.

Examples:

'System.Array' denotes the .NET class System.Array

'array(bool)' denotes an array of boolean

'System.String[]' denotes an array of string


Using the SWICLI 1.x Prolog API

creating instances of .NET classes

To create an instance of a .NET class from within Prolog, call cli_new(+Class,+Params,-Ref) with a classname, a list of actual parameters for the constructor, and a variable to be bound to the new reference, e.g.

cli_new( 'System.Forms.Frame', ['frame with dialog'], F)

which binds F to a new object reference, e.g.

 @('C#0008272420')

(not that the details of this structure are of any necessary concern to the Prolog programmer or to the applications she writes).
NB for convenience, this predicate is overloaded: Class can also be a class type in structured notation, e.g. 
array(boolean).


calling methods of .NET objects or classes

The object reference generated by the cli_new/3 call (above) can be passed to other SWICLI API predicates such as

cli_call( +Ref, +Method, +Params, -Result)

 e.g.

cli_call( F, setVisible, [@(true)], _)

which calls the setVisible method of the object to which F refers, effectively passing it the .NET value true.

(This call should display the new JFrame in the top left corner of the desktop.)

Note the anonymous variable passed as the fourth argument to cli_call/4.  A variable in this position receives the result of the method call: either a value or a reference.  Since SetVisible() is a void method, the call returns the (artificial) reference @(void).

Some may prefer to code this call thus:

cli_call( F, setVisible, [@true], @void)

which documents the programmer's understanding that this is a void method (and fails if it isn't :-).
 
If the +Ref argument represents a class, then the named static method of that class  is called.


Fetching field and property values of .NET objects or classes

The cli_get/3 API predicate can retrieve the value of an instance field or a static field, e.g.

��� cli_get( 'System.Color', pink, Pink)

which binds the Prolog variable Pink to a reference to the predefined System.Drawing.Color "constant" which is held in the static final .pink field of the System.Drawing.Color class.

More generally, cli_get/3 has the following interface:

cli_get( +Class_or_Object, +Field, -Datum)

If the first argument represents a class, then a static field of that class with FieldName is accessed.


Setting field or properties values of .NET objects or classes

Object and class fields can be set (i.e. have values or references assigned to them) by the cli_set/3 API procedure, which has the following interface:

cli_set( +Class_or_Object, +Field, +Datum)

where Datum must be a value or reference of a type suitable for assignment to the named field of the class or object.


a slightly longer example

This code fragment

    findall(
        Ar,
        (   current_prolog_flag( N, V),
            term_to_atom( V, Va),
            cli_new( '[LSystem.String;', [N,Va], Ar)
        ),
        Ars
    ),
    cli_new( '[[LSystem.String;', Ars, Ac),
    cli_datums_to_array( [name,value], Ah),
    cli_new( 'System.Forms.Frame', ['current_prolog_flag'], F),
    cli_call( F, getContentPane, [], CP),
    cli_new( 'System.Forms.Table', [Ac,Ah], T),
    cli_new( 'System.Forms.ScrollPane', [T], SP),
    cli_call( CP, add, [SP,'Center'], _),
    cli_call( F, setSize, [600,400], _),!.
 

builds an array of arrays of strings containing the names and values of the current SWI-Prolog "flags", and displays it in a JTable within a ScrollPane within a JFrame:

 


 

 

In addition to SWICLI API calls, this code calls cli_datums_to_array/2, a utility which converts any list of valid representations of .NET values (or objects) into a new .NET array, whose base type is the most specialised type of which all list members are instances, and which is defined thus:

 

cli_datums_to_array( Ds, A) :-
    ground( Ds),
    cli_datums_to_most_specific_common_ancestor_type( Ds, T),
    cli_new( array(T), Ds, A).
 

Having found the "most specific common ancestor type" (my phrase :-), a new array of this type is created, whose elements are initialised to the successive members of the list of datums.

This illustrates another mode of operation of cli_new/3:

cli_new( +ArrayType, +InitialValues, -ArrayRef)

See the relevant Appendix for fuller details of the API procedures.

Don't forget the possibility of writing and manipulating new .NET classes to serve your Prolog applications: this interface is not designed to make .NET programming redundant :-)



cli_new( +X, +Argz, -V) :-

X can be:

  • a suitable type
    • i.e. any class(_,_)array(_) or primitive type (e.g. byte but not void)
  • an atomic classname
    • e.g. 'System.String'
    • e.g. 'LSystem.String;'   (a redundant but legitimate form)
  • an atomic descriptor
    • e.g. '[I'
  • a class object
    • i.e. an object whose type is  class([.NET,lang],['Class'])

if X denotes a primitive type and Argz is castable to a value of that type, then V is that value (a pointless mode of operation, but somehow complete...)

if X denotes an array type and Argz is a non-negative integer, then V is a new array of that many elements, initialised to the appropriate default value

if X denotes an array type and Argz is a list of datums, each of which is (independently) castable to the array element type, then V is a new array of as many elements as Argz has members, initialised to the results of casting the respective members of Argz

if X denotes a non-array object type and Argz is a list of datums, then V is the result of an invocation of that type's most specifically-typed constructor to whose respective parameters the members of Argz are assignable



cli_call( +X, +Method, +Args, -R) :-

X can be:

�  typeclass object or classname (for static methods of the denoted class, or for static or instance methods of System.Class)

�  a class instance or array (for static or instance methods)

Method can be:

�  an atomic method name (if this name is ambiguous, as a result of method overloading, then it will be resolved by considering the types of Args, as far as they can be inferred)

�  an integral method index (untested: for static overload resolution)

�  methodID/1 structure (ditto)

Args must be

  • a proper list (possibly empty) of ground arguments

Finally, an attempt will be made to unify R with the returned result.



cli_set( +X, +Field, +V) :-

basically, sets the Fspec-th field of object X to value V

X can be:

  • class object, a classname, or an (object or array) type (for static fields, or System.Class fields)
  • class instance (for non-static fields)
  • an array (for indexed element or subrange assignment)
  • but not a string (no fields to retrieve)

Field can be:

  • an atomic field name (overloading will be resolved dynamically, by considering the inferred type of V)
  • an integral field index (static resolution: not tried yet)
  • fieldID/1 (static resolution: not tried yet)
  • a variable (field names, or array indices, are generated)(?!)
  • an array index I (X must be an array object: X[I] is assigned V)
  • a pair I-J of integers (J can be a variable) (X must be an array object, V must be a list of values: X[I-J] will be assigned V)

V must be ground (although one day we may pass variables to SWICLI?!)



cli_get( +X, +Field, -V) :-

X can be:

  • class object, a classname, or an (object or array) type (for static fields, or System.Class fields)
  • class instance (for non-static fields)
  • an array (for the 'length' pseudo field, or for indexed element retrieval)
  • but not a String (clashes with classname; anyway, System.String has no fields to retrieve)

Field can be

  • an atomic field name
  • or an integral field index (these are a secret :-)
  • or a fieldID/1 (not for general consumption :-)
  • or an integral array index (high-bound checking is done by .NET, maybe throwing an exception)
  • or a variable (field names, or array indices, are generated)
  • or a pair I-J of integers or variables (array subranges are generated) (relational or what?!)

Immediately before cli_get/4 returns, an attempt will be made to unify V with the internally computed result.

 


exceptions thrown by .NET

Uncaught exceptions thrown by the .NET in the course of handling a SWICLI 3.x Prolog API call are mapped onto Standard Prolog exceptions, e.g.

cli_new( 'Systen.DateTime', [yesterday], D)

raises the Prolog exception

cli_exception('System.IllegalArgumentException', @'C#0008408972')

because, as the exception suggests, yesterday is not a valid constructor argument.
 
.NET exceptions are always returned as Prolog exceptions with this structure:

cli_exception( classnamereference_to_exception_object)

 


 

cli_add_event_handler( +Class_or_Object, +EventName, +PredicateIndicator) :-

 

ADDING A NEW EVENT HOOK

 

We already at least know that the object we want to hook is found via our call to

 

?- botget(['Self'],AM).

 

So we ask for the e/7 (event handlers of the members)

 

?- botget(['Self'],AM),cli_memb(AM,e(A,B,C,D,E,F,G)).

 

�Press ;;;; a few times until you find the event Name you need (in the B var)

 

A = 6,����������������������������������������� % index number

'IM',������������������ ��������������������% event name

C = 'System.EventHandler'('InstantMessageEventArgs'),�� % the delegation type

['Object', 'InstantMessageEventArgs'],����� % the parameter types (2)

E = [],���������������������������������������� % the generic paramters

F = decl(static(false), 'AgentManager'),������� % the static/non static-ness.. the declaring class

G = access_pafv(true, false, false, false)����� % the PAFV bits

 

 

So reading the parameter types� "['Object', 'InstantMessageEventArgs']" lets you know the predicate needs at least two arguments

 

And "F = decl(static(false), 'AgentManager')" says add on extra argument at start for Origin

 

� handle_im(Origin,Obj,IM)

 

So registering the event is done:

 

?- botget(['Self'],AM), cli_add_event_handler(AM,'IM',handle_im(_Origin,_Object,_InstantMessageEventArgs))

 

To target a predicate such as:���� handle_im(Origin,Obj,IM):-writeq(handle_im(Origin,Obj,IM)),nl.

 


We have 3 different ways to denote Types in the system:

Type: �SWICLI type, e.g. char, byteclass(['System'],['String'])boolean, array(boolean)

Typeref: �The @('C#345345345')� that points to an instance of System.Type

Typename: �The 'System.Char', 'System.Boolean','System.Boolean[]'


Conversions between the three

cli_typeref _to_typename+Class, -Classname)

Class must be a SWICLI reference to a .NET class object (i.e. an instance of System.Type); Classname is its canonical dotted name, e.g. 'System.Collections.Date'.
 

cli_typeref_to_type+Class, -Type)

Class must be a SWICLI reference to a .NET class object (i.e. an instance of System.Type); Type is its SWICLI type, e.g. class(['System'],['DateTime']) or array(double).
 

cli_typename_to_typeref+Classname, -Class)

Classname must be a canonical dotted name (an atom) of a .NET class, e.g. 'System.Date'Class is a SWICLI reference to a corresponding .NET class object (i.e. an instance of System.Type).
 

cli_typename_to_type+Classname, -Type)

Classname must be a canonical dotted name (an atom) of a .NET class, e.g. 'System.Collections.Date'Type is its SWICLI type, e.g. class(['System'],['DateTime']).
 

cli_type_to_typeref+Type, -Class)

Type is a SWICLI class (or array) type, e.g. class(['System','Data','Sql'],['Timestamp']) or array(boolean)Class is a SWICLI reference to a .NET class object (an instance of System.Type) which corresponds to Type.
 

cli_type_to_typename+Type, -Classname)

Type is a SWICLI class (or array) type, e.g. class(['System','Data','Sql'],['Timestamp']) or array(boolean)Classname is its canonical dotted name (an atom).


Object Type Checking

 

cli_object_is_typeref+Object, ?Class) ��AKA:� cli_get_type/2

Object is a SWICLI reference to a .NET object; Class is a SWICLI reference to a .NET class object (an instance of System.Type) which represents Object's class.
 

cli_object_is_type+Object, ?Type) ��AKA:� cli_is_type/2

Object is a SWICLI reference to a .NET object; Type is its SWICLI type, e.g. array(boolean)class(['System','Data','Sql'],['Timestamp']).
 

cli_object_is_typename+Object, ?Classname) ���AKA: cli_get_typename/2

Object is a SWICLI reference to a .NET object; Classname is its canonical dotted name (an atom).. 


cli_datum_to_type
+Datum, ?Type)

Datum must be a valid SWICLI representation of some .NET object or value e.g. 3fred@(false)Type is its SWICLI type, e.g. char_byteclass(['System'],['String'])boolean.


cli_ref_to_type
+Ref, ?Type)

Ref is a SWICLI reference to a .NET object; Type is the SWICLI type of Object, e.g. array(boolean)class(['System','Data','Sql'],['Timestamp']).


Inspection of Terms denoting Objects

 

cli_primitive_type-Type)

Type is one of the SWICLI primitive types booleancharbyteshortintlongfloatdouble.
 

cli_is_typeref?Term)

Term is a SWICLI reference to a .NET class object, i.e. to an instance of System.Type. No further instantiation of Term will take place; if it is not ground, this predicate fails. 


cli_is_object?Term)

Term is a SWICLI reference to a .NET object. No further instantiation of Term will take place; if it is not ground, this predicate fails.
 

cli_is_object_type?Term) ��

Term is a SWICLI class or array type (but not nullvoid, or one of the primitive types).  No further instantiation of Term will take place; if it is not ground, this predicate fails.

cli_is_ref?Term)

Term is a SWICLI class or array type, or is null (i.e. the SWICLI type of .NET's null reference) (but not void or one of the primitive types).  No further instantiation of Term will take place; if it is not ground, this predicate fails.

cli_is_type?Term)

Term is a SWICLI type, e.g. char_bytefloatarray(int).  No further instantiation of Term will take place; if it not ground, this predicate fails. 


Inspection of Terms denoting Values

 cli_void-Datum)

Datum is the SWICLI representation of the (notional but convenient) .NET value void, i.e. @(void).

 

cli_false-Datum)

Datum is the SWICLI representation of the .NET boolean value false, i.e. @(false).
 

cli_true-Datum)

Datum is the SWICLI representation of the .NET boolean value true.
 

cli_is_false?Term)

Term is the SWICLI representation of the .NET boolean value false. No further instantiation of Term will take place; if it is not ground, this predicate fails.
 

cli_is_null?Term)

Term is a SWICLI representation of the .NET boolean value null. No further instantiation of Term will take place; if it is not ground, this predicate fails.
 ����������

cli_is_true?Term)

Term is the SWICLI representation of the .NET boolean value true.  No further instantiation of Term will take place; if it is not ground, this predicate fails.
 

 

cli_is_void?Term)

Term is the SWICLI representation of the (notional but convenient) .NET value void, i.e. @(void).  No further instantiation of Term will take place; if it not ground, this predicate fails.
 

cli_null-Datum)

Datum is the SWICLI representation of the .NET null reference null.
 

Utilities

 cli_array_to_length+Array, -Length)

Array is a SWICLI reference to a .NET array;  Length is its length (an integer).

 cli_array_to_list+Array, -ListOfDatums)

Array is a SWICLI reference to a .NET array (of any base type); ListOfDatums is a (Prolog) list of SWICLI references to, or values of, its respective elements.
 

cli_datums_to_array+ListOfDatums, -Array

ListOfDatums is a (Prolog) list of SWICLI references or values; Array is a SWICLI reference to a .NET array of corresponding objects or values.  The base type of Array is the most specific .NET type of which each member of ListOfDatums is (directly or indirectly) an instance. If there is no such type, this predicate fails. Values of .NET primitive types are not automatically "boxed". Lists which are mixtures of numbers, booleans and object references cannot be converted to .NET arrays with this predicate.

 cli_enumeration_element+Enumeration, -Element

Enumeration is a SWICLI reference to a .NET object whose class implements the System.Collections.Enumeration interface; Element is an element of Enumeration.  This predicate can generate each element of an enumeration.

cli_enumeration_to_list+Enumeration, -ListOfElement)

Enumeration is a SWICLI reference to a .NET object whose class implements the System.Collections.Enumeration interface;  ListOfElement is a list of SWICLI references to each element of Enumeration.

 cli_hashtable_pair+Hashtable, -KeyValuePair)

Hashtable is a SWICLI reference to a .NET hashtable object (an instance of System.Collections.Hashtable); KeyValuePair is a -/2 compound term whose first arg is a key (atom or ref) from Hashtable, and whose second arg is its corresponding value (atom or ref), e.g.fred-@'J#0008127852'.
 

cli_iterator_element+Iterator, -Element)

Iterator is a SWICLI reference to a .NET object whose class implements the System.Collections.Iterator interfaceElement is a SWICLI reference to one of its elements.  This predicate can generate all elements.
 

cli_list_to_array+ListOfDatum, -Array)

This is a synonym for cli_datums_to_array/2, in case you forget that SWICLI values and references are called "datums".
 

cli_map_element+Map, -KeyValuePair)

Map is a SWICLI reference to a .NET object whose class implements the System.Collections.Map interface; KeyValuePair is a -/2 compound term whose first arg is a key (atom or ref) from Map, and whose second arg is its corresponding value (atom or ref), e.g. -(fred,@'J#0008127852'), or fred-@'J#0008127852' using conventional operator definitions.
 

cli_set_element+Set, -Element)

Set is a SWICLI reference to a .NET object whose class implements the System.Collections.Set interface; Element is a SWICLI reference to an object (or null) within Set.  This predicate can generate all elements of Set

 

to do

Apart from any bugs I don't know about, this interface is usable and useful as it stands.  Nevertheless there are some things "to do" at some stage in the future


Douglas R. Miles
drafted 10th April 2012

 

Douglas Miles

unread,
Jan 6, 2016, 8:10:04 AM1/6/16
to SWI-Prolog, logi...@gmail.com
Although you see documentation in my mail (that is only the C#/Sharp use) you are not seeing documentation for the Native C/C++  capabilities swicli/swicffi has to use .so(s) and .dll(c) .dynlib(s)

The reason I felt the project was important is it gives Prolog the same abilities that Python has for accessing precompiled libraries at runtime ( people complain Prolog does not have any ability) 

Douglas Miles

unread,
Jan 6, 2016, 12:05:58 PM1/6/16
to swi-p...@googlegroups.com, logi...@gmail.com
Sorry to keep replying to my own messages..

When I say I don't have the time, what I meant to say is not having the time to make it more awesome.  
I have plenty of time to keep the it from bitrotting and bug fixing.


Off the top of my what could be done is:


1) Porting of the Prolog-only parts Sicstus structs package order to use this library.

2) Better support of drop-in loading of *.cffi files.  (And finishing the def<whatnot>s )

3) SWI-Prolog 6.6.6 vs 7.x  PlList construction/destructuring.  <- I will fix this the first sign of trouble

4) Potentially packages/swcli  build scripts (right now it's a pack but might be better distributed like JPL)

5) More documentation and examples.

6) Since it can create "Classes/Structs" some object library like LogTalk and 'PLO' to manage the declarations
    



rausm

unread,
Jan 6, 2016, 2:49:57 PM1/6/16
to SWI-Prolog, logi...@gmail.com
> you are not seeing documentation for the Native C/C++  capabilities swicli/swicffi has to use .so(s) and .dll(c) .dynlib(s)

Terrific,  I always wanted dynamic FFI for swipl. And although I was aware of SWICLI, I always thought that the "native access capabilities" meant "use P/Invoke".

I'll try it out sometimes soon (perhaps over the weekend, time allowing), and if successful, I'll try to write some example. I might even try to wrap IUP (http://www.tecgraf.puc-rio.br/iup). Although XPCE is great, it's not getting any younger, while IUP is constantly developed.

My dream is IUP + Logtalk ==> Next-gen XPCE.

Thank you for making your work available.

Douglas Miles

unread,
Jan 6, 2016, 4:08:01 PM1/6/16
to SWI-Prolog, logi...@gmail.com

On Wednesday, January 6, 2016 at 11:49:57 AM UTC-8, rausm wrote:
> you are not seeing documentation for the Native C/C++  capabilities swicli/swicffi has to use .so(s) and .dll(c) .dynlib(s)

Terrific,  I always wanted dynamic FFI for swipl. And although I was aware of SWICLI, I always thought that the "native access capabilities" meant "use P/Invoke".



It is actually P/Invoke behind the scenes, difference is instead of telling you "use P/Invoke". which means asking you to create a wrapper class myPinvoke.cs and compiling it ... is that swicli uses Runtime.IForget to create a stub behind the scenes (specified by prolog's first call)
and then adds it to the dictionary stored @'C#967' .. Then when cli_call/4 is called and the first arg is a dictionary of function signatures it dispatches on the one matching name/params.


[DllImport ("libc.so")] private static extern int getpid ();

?- cli_get_dll('libc.so.6',DLL),cli_call(DLL,gitpid,[],O).
DLL = @'C#967',
O = 1277.


you have in your PATH libMyLibrary.dylib

[DllImport ("MyLibrary")] private static extern void Frobnicate (char * w);

?- cli_get_dll('libMyLibrary.dylib',DLL),cli_call(DLL,'Frobnicate',["Foo"],O).
DLL
= @'C#968',
O
= @void.


 
My dream is IUP + Logtalk ==> Next-gen XPCE.

Awesome idea!

rausm

unread,
Jan 11, 2016, 9:01:27 AM1/11/16
to SWI-Prolog, logi...@gmail.com
Sadly, both 32bit & 64bit (windows) versions are linked against debug vcrt libraries which are not redistributable (not available for simple download; and I don't currently have VC++ parts of VS installed).

Attaching (perhaps useless) sxstrace outputs.
32bit.txt
64bit.txt

Douglas Miles

unread,
Jan 11, 2016, 1:19:59 PM1/11/16
to rausm, SWI-Prolog
Did this URL https://www.microsoft.com/en-us/download/confirmation.aspx?id=29  work  or was it still; missing the debug versions?


Douglas Miles

unread,
Jan 11, 2016, 2:04:28 PM1/11/16
to rausm, SWI-Prolog
By the end of week I hope to rebuild .. this time I wont build as debug.

rausm

unread,
Jan 11, 2016, 3:07:45 PM1/11/16
to SWI-Prolog, milosl...@gmail.com, logi...@gmail.com
> Did this URL https://www.microsoft.com/en-us/download/confirmation.aspx?id=29  work  or was it still; missing the debug versions?

That redist I already had. (Did repair and retried both 32 and 64 bit just to be ultra sure).
Debug versions of MS runtimes are not distributed (or even allowed to be re-distributed by third parties), so no luck.


> By the end of week I hope to rebuild .. this time I wont build as debug.

Please, notify the mailing list, I'll retry.

Douglas Miles

unread,
Jan 11, 2016, 11:53:31 PM1/11/16
to swi-p...@googlegroups.com, milosl...@gmail.com, logi...@gmail.com
Binaries are rebuilt  https://github.com/logicmoo/swicli.git   


With the Release versions now.. I was only able to test on win64

rausm

unread,
Jan 20, 2016, 4:06:55 PM1/20/16
to SWI-Prolog, milosl...@gmail.com, logi...@gmail.com
Sorry for the silence, I was offlne during vacation. I tried the 64bit version, works a-ok (I'll try the 32bit sometimes, the bitness of the OS shouldn't matter, and it should work anyways).

When I tried IUP, I succeeded only partly. I am able to load the library, and call the "hello world" IupMessage without crashing, but only the first letters of the windows label & message contents are shown. I suppose it has to do with how swipl internally represents characters. While on linux (and Mac, I waguely remember), it is UTF-8, on Windows x<whatever> it will be UTF-16 (so the "additional" zero's will terminate the string for "local ANSI" or UTF-8 oriented IUP).

Is there something I could use as a workaround ? (if my assumption this would better be "fixed" in the library is correct ...)

Cheers,

 M.R.

Dne úterý 12. ledna 2016 5:53:31 UTC+1 Douglas Miles napsal(a):

Jan Burse

unread,
Jan 21, 2016, 7:58:01 AM1/21/16
to SWI-Prolog, milosl...@gmail.com, logi...@gmail.com
Concerning: First Generation FFIs,
Second Generation FFIs, Third Generation FFIs

Hi,

In my opinion instead of:
?- ..., cli_call(DLL,'Frobnicate',["Foo"],O).

It would be better to once define a SWI-Prolog predicate that
calls this. Since I guess the cli_call/4 will search true the
RTTI (Runtime Type Information), and do this each time it is
invoked.

On the other hand if you have something, like:
:- ..., foreign(frobnicate/2, DLL, 'Frobnicate').

And if somehow the RTTI (Runtime Type Information) is precalculated,
you can call:

?- frobnicate("Foo", X).

very quickly. Also in loops. And with the help of foreign/3
you can even bootstrap an auto loader.

Just saying, I know a couple of Prolog systems with have
this know FFI, very dynamic, with the possibly unpleasant
consequence that it is kind of slow.

But I might be wrong here, but usually doing RTTI lookup
once and not in every call is faster, much faster.

Lets generate some hype: Lets call the dynamic thing 1G
FFI, the foreign directive 2G FFI, and the auto loader 3G
FFI.

3G FFIs are now widespread, for example Matlab can do
it with Java, etc.. (don't have hands on, only from reading
a corresponding doc)

Bye

Jan Burse

unread,
Jan 21, 2016, 8:02:23 AM1/21/16
to SWI-Prolog
See also:

How Common are Auto Loaders? The MATLAB Case
https://plus.google.com/+JanBurse/posts/VH5BvvhQjxP

Jan Burse

unread,
Jan 21, 2016, 8:19:57 AM1/21/16
to SWI-Prolog, milosl...@gmail.com, logi...@gmail.com

The issue is discussed here:
https://lotsacode.wordpress.com/2010/04/13/reflection-type-getproperties-and-performance/

But this is already an old post. But usually the reflection
calls are not made to be ultrafast, so I guess the issue is
still here in 2016 ...

The problem with a foreign/3 you have to go deeper into
the SWI Kernel. Its not just some other new predicate.
Its a predicate that works with the SWI predicate table
structure. So its non-trivial.

In Jekejeke this predicate table structure is not public,
it belongs currently to the internal API, but its already
quite generic. It resolves around plugable delegates.

So a predicate is basically in Jekejeke:

    Predicate struct {
         /* stuff that is of interest to the interpreter,
             like name, arity etc.. of the predicate  */
         /* the delegate does the real work when
            invoking the predicate */
         Delegate del;
     }

Bye

Douglas Miles

unread,
Jan 21, 2016, 1:48:42 PM1/21/16
to Jan Burse, SWI-Prolog, Miloslav Raus
On Thu, Jan 21, 2016 at 4:58 AM, Jan Burse <burs...@gmail.com> wrote:
Concerning: First Generation FFIs,
Second Generation FFIs, Third Generation FFIs

Hi,

In my opinion instead of:
?- ..., cli_call(DLL,'Frobnicate',["Foo"],O).

It would be better to once define a SWI-Prolog predicate that
calls this. Since I guess the cli_call/4 will search true the
RTTI (Runtime Type Information), and do this each time it is
invoked.

On the other hand if you have something, like:
:- ..., foreign(frobnicate/2, DLL, 'Frobnicate').

And if somehow the RTTI (Runtime Type Information) is precalculated,
you can call:

?- frobnicate("Foo", X).

instead of calling  ?- cli_call(DLL,'Frobnicate',["Foo"],O).

One instead may call:
?- cli_find_method(DLL,'Frobnicate'("Foo"),MH),
   cli_call(MH,'Frobnicate'("Foo"),O).

MH is a Method Handle.  What you are suggesting is that the programmer could 
assert(( frobnicate(Foo, O):- cli_call(MH,v(Foo),O)   )).

You are correct, now frobnicate("hello", O) would end up being faster as it no longer using the slow method search.

 

Douglas Miles

unread,
Jan 21, 2016, 1:56:36 PM1/21/16
to rausm, SWI-Prolog
On Wed, Jan 20, 2016 at 1:06 PM, rausm <milosl...@gmail.com> wrote:
Sorry for the silence, I was offlne during vacation. I tried the 64bit version, works a-ok (I'll try the 32bit sometimes, the bitness of the OS shouldn't matter, and it should work anyways).

When I tried IUP, I succeeded only partly. I am able to load the library, and call the "hello world" IupMessage without crashing, but only the first letters of the windows label & message contents are shown. I suppose it has to do with how swipl internally represents characters. While on linux (and Mac, I waguely remember), it is UTF-8, on Windows x<whatever> it will be UTF-16 (so the "additional" zero's will terminate the string for "local ANSI" or UTF-8 oriented IUP).

Is there something I could use as a workaround ? (if my assumption this would better be "fixed" in the library is correct ...)




replace your  cli_call   with a cli_find_method/3 this will allow you to inspect the chosen method handle.   

so for example 

?-cli_call(..,make_dialog_box,['OK_CANL_BUTTON',Message,Title],_).

becomes:

?- cli_find_method(..,make_dialog_box('OK_CANL_BUTTON',Message,Title),MH), cli_writeln(MH).     
    
   Will describe the method it is choosing.

Jan Burse

unread,
Jan 21, 2016, 5:16:10 PM1/21/16
to SWI-Prolog, burs...@gmail.com, milosl...@gmail.com, logi...@gmail.com
Maybe I don't understand every detail. I was also looking up the LISP
precursor to your code. Very fascinating the LISP thingy and your
SWICLI contribution. So please don't misunderstand my nagging.

There is a little unsatisfactory mention of defc as a marco for a foreign
funcall defined LISP function. Basically an even worse solution than
asserting a method handle, which is already a progress.

But I still have a lot of questions:

1) Sure find method takes actual arguments and not formal parameters?

2) Sure call with a method handle still needs a method name?

3) Sure assert is a good approach, it incures overhead of local
    Prolog variables and a call of an other predicate (here cli_call),
    instead of directly jumping into the method handle with the
    actual parameters.

    I guess a compiler cannot eliminate the overhead since cli_call
    is opaque for the compiler, oven a dumb interpreter cannot
    inline it since its not written in Prolog.

    So we would need some PL_define_by_method_handle at
    runtime from the Prolog vendor, lets say this is wrapped in
    some cli_register API. Could then go on:

    foreign(Indicator, Class, Signature) :-
        cli_find_method(Class, Signature, MH),
        cli_register(Indicator, MH).

    (assuming it is searching all DLLs in a class path
    setting, so no DLL parameter)

Bye

Jan Burse

unread,
Jan 21, 2016, 5:25:25 PM1/21/16
to SWI-Prolog, burs...@gmail.com, milosl...@gmail.com, logi...@gmail.com
Remark: It will be of course not the original MH from the
target language,

it will still be a delegate with some extra, since it needs to
translate actual parameters, return values, maybe handle
non-determinism etc.. etc..

And it will be a delegate that fits in the PL_define_by_method_handle.
Remember the Pythonesk OO convetion in making explicit the
self and passing it in the first argument, now what is the difference
between:

1) PL_define_by_procedure
2) PL_define_by_method_handle

Well the difference is as follows. In PL_define_by_procedure there
is no self, there is no self for a method handle, so all that is needed
is jumping into the procedure with the arguments.

In PL_define_by_method_handle, what is registered is a delegate,
so when calling the callback of the delegate, we also have to pass
the delegate itself. So what is needed is jumping into the callback with
the delegate AND the arguments.

Why would we pass the delegate as well?

Well the delegate might contain further info, which allow the method
handle to execute. We will possibly not be able to create for each
method a new callback location in the memory (Would require on
the fly compilation to machine code).

But we might create for each method a delegate object somewhere
and with a more generic callback (Requires only OO and reflection,
as SWICLI already masters).

Bye

Jan Burse

unread,
Jan 21, 2016, 6:06:39 PM1/21/16
to SWI-Prolog, burs...@gmail.com, milosl...@gmail.com, logi...@gmail.com
Hi,

What I wrote made me currious whether SWI Prolog hasn't really
delegate registering. It seems that it hasn't, I find flags and meta
predicate signature as arguments for registering:

    SWI-Prolog, Registering Foreign Predicates
    http://www.swi-prolog.org/pldoc/man?section=foreign-register-predicate

But no delegate object. Also the context argument that is passed
to a foreign procedure is not the same as a delegate. Its only
the Prolog context for non-determinstic calls.

I understand registering flags and meta at the same time has
some advantage. In the case of Jekejeke I am delaying the
association of a predicate with a delegate a little bit, some
code looks as follows:

/**
* <p>Define a built-in for a predicate.</p>
*
* @param pick The predicate.
* @param del The delegate.
*/
public static void defineProvable(Predicate pick,
Delegate del) {
/* determine static flag */
if ((pick.getBits() & Predicate.MASK_PRED_VIRT) == 0)
del.subflags |= Delegate.MASK_DELE_NORC;
/* promote the builtin */
Predicate.checkUnsealed(pick);
Delegate.promoteBuiltin(pick, del);
if (!del.equals(pick.del))
throw ...;
}

The Predicate.checkUnsealed is a multifile guard and Delegate.promoteBuiltin
has to do with multi-threading. The later has to do with it, that there should be
a certain monotonocity for a predicate in going from undef to defined
by a delegate.

The deferal of the promotion allows having a new virtual/1 directive (the
Predicate.MASK_PRED_VIRT flag, similar to the static modifier in Java
but with the converse meaning). Currently only used in translating between
evaluable functions and predicates.

Bye

Am Donnerstag, 21. Januar 2016 23:25:25 UTC+1 schrieb Jan Burse:
1) PL_define_by_procedure
2) PL_define_by_method_handle

Douglas Miles

unread,
Jan 21, 2016, 7:32:48 PM1/21/16
to Jan Burse, SWI-Prolog, Miloslav Raus
On Thu, Jan 21, 2016 at 2:16 PM, Jan Burse <burs...@gmail.com> wrote:
Maybe I don't understand every detail. I was also looking up the LISP
precursor to your code. Very fascinating the LISP thingy and your
SWICLI contribution. So please don't misunderstand my nagging.

There is a little unsatisfactory mention of defc as a macro for a foreign
funcall defined LISP function.
Basically an even worse solution than
asserting a method handle, which is already a progress.

The lispy parts are to use "*.cffi" files since SWIG has an output type of cffi .  I figure more often the prolog programmer is going to want and need a way to import quickly a set of foreign functions once without much effort.  Since they are going be so much time and thought into using the C library.

But in the long run the right goal is to  shoot for supporting SICStus Interface and following Mercury's :-pragma/1 system  since it has support for foreign_proc (amounts to defc)

So we have a tool that converts C/C++ projects or headers to Prolog's :-pragma/1 then we could gladly remove traces of the CFFI.



But I still have a lot of questions:

1) Sure find method takes actual arguments and not formal parameters?


Either "actual arguments" or not "formal parameters" .. That is the cli_find_method/3 more sanely should be by using the "formal parameters"   I just didn't make this a requirement.      I gave the example using  "actual arguments" becasue I hadn't wanted to write "this is a string"     partially I didn't want to miss a MethodHandle with  "const(pointer(char))"  or "pointer(wchar)" but the rationalized version for search is 'System.String' .   As you can guess  "formal parameters" is a faster search because "actual arguments" allows a bit more leniency. 



2) Sure call with a method handle still needs a method name?


Call  with a  method handle is actually done via anonymous closure so the name is optional. If one uses the method name it ends up being ignored.



3) Sure assert is a good approach, it incurs overhead of local
    Prolog variables and a call of an other predicate (here cli_call),
    instead of directly jumping into the method handle with the
    actual parameters.

    I guess a compiler cannot eliminate the overhead since cli_call
    is opaque for the compiler, oven a dumb interpreter cannot
    inline it since its not written in Prolog.

Oh, cli_* functions are implemented are direct and yes you can actually bind a method handle directly to a predicate name.

I Implemented that in this code .  So actually once you have your method handle is 
 
?- cli_find_method(DLL,'Frobnicate'("Foo"),MH),
   cli_call('Swicli.Library.PrologCLR','InternMethod'("frob_mod","frobnicate",MH,@null),_).

?- listing(frobnicate).

% Foreign: frob_mod:frobnicate/1

Which actually makes more sense as arity 1 since frobnicate is declared as 

"__cdecl void Frobnicate(const char* txt);"



    So we would need some PL_define_by_method_handle at
    runtime from the Prolog vendor, lets say this is wrapped in
    some cli_register API. Could then go on:

    foreign(Indicator, Class, Signature) :-
        cli_find_method(Class, Signature, MH),
        cli_register(Indicator, MH).

    (assuming it is searching all DLLs in a class path
    setting, so no DLL parameter)

   ?- cli_find_method(DLL,'Frobnicate'("Foo"),MH), 
cli_intern_method("frob_mod","frobnicate",MH,@null).





-Douglas

Douglas Miles

unread,
Jan 21, 2016, 8:54:07 PM1/21/16
to Jan Burse, SWI-Prolog, Miloslav Raus
On Thu, Jan 21, 2016 at 2:25 PM, Jan Burse <burs...@gmail.com> wrote:
Remark: It will be of course not the original MH from the
target language,


Correct in the case of  language smoothing delegate like: 

C/C++ its a PInvokeDelegate
Java it is a    IKVM.misc.unsafe.MethodHandle
C#,F#  Delegate<>




it will still be a delegate with some extra, since it needs to 
translate actual parameters, return values, maybe handle 
non-determinism etc.. etc..


Then I have a PL_register_foreign_in_module compatible delegates in which SWI-Prolog  understands.. Then i make a Adapter to contain the correct number of   PL_get_* PL_unify_* s  PL_cons* PL_put_*  to deal with the arguments that are "input" vs "output" arguments.   sometimes I  PL_open/close_foriegn  Also in cases of exceptions I convert the foreign exceptions to prolog ones.  And some of that code happens from a chain of Action<>s I create on the fly but supply them to be ran After the C function is complete before I can decide to unify the output params.  For example Action<>  when the output params cannot unify with any params sent in.

 No-det was the funnest to implement 


 

And it will be a delegate that fits in the PL_define_by_method_handle.
Remember the Pythonesk OO convetion in making explicit the
self and passing it in the first argument, now what is the difference
between:

1) PL_define_by_procedure
2) PL_define_by_method_handle

Well the difference is as follows. In PL_define_by_procedure there
is no self, there is no self for a method handle, so all that is needed
is jumping into the procedure with the arguments.


Well this shows you are probably deducing why I needed at times 
  cli_find_method to be durable for uses where I have "method arguments". since the method handle for an interface type with interface argument  might be different than very different than the implementation types on the actual classes and it is possible that a corrector actual method exists/

 

In PL_define_by_method_handle, what is registered is a delegate,
so when calling the callback of the delegate, we also have to pass
the delegate itself. So what is needed is jumping into the callback with
the delegate AND the arguments.

Why would we pass the delegate as well? 

Well the delegate might contain further info, which allow the method
handle to execute. 
We will possibly not be able to create for each
method a new callback location in the memory (Would require on
the fly compilation to machine code).


To avoid machine compilation made a todo list of closures of my most frequent operations (PL_put PL_get etc)    deduced from comparing the C method to what SWI's FFI needed and after most methods 


I run those.


But we might create for each method a delegate object somewhere
and with a more generic callback (Requires only OO and reflection,
as SWICLI already masters).

A lot of this I know was written before noticing I am on the fly compiling post call hooks

Douglas Miles

unread,
Jan 21, 2016, 9:27:02 PM1/21/16
to Jan Burse, SWI-Prolog, Miloslav Raus
To avoid machine compilation made a todo list of closures of my most frequent operations (PL_put PL_get etc)    deduced from comparing the C method to what SWI's FFI needed and after most methods 


In case anyone was wondering what I meant by this,...  here is such an example.. 



Jan Burse

unread,
Jan 22, 2016, 4:57:23 AM1/22/16
to SWI-Prolog, burs...@gmail.com, milosl...@gmail.com, logi...@gmail.com
Looks like on the fly code generation is involved, here is an example:

    https://github.com/logicmoo/swicli/blob/master/c/Swicli.Library/PInvokeMetaObject.cs#L414-L455

Otherwise delegates wouldbn't work if SWI has only function pointer registration.

But still difficult for me to follow the flow, there are also competing register
entry points, such as libpl.PL_register_foreign_in_module and PlEngine.RegisterForeign.
Last but not least class names seem to be case insensitive, what the file names
on disk consider, hurts my eyes ... Brrr

Assuming now that the solution is based on on the fly code generation, my
claim here is still, that if SWI would already provide a delegate interface, this
would not be necessary. Possibly allowing CLI like interfaces also to C++
with a more minimal RTTI (Runtime Type Information), that doesn't
allow on the fly code generation.

On the other hand on the fly code generation, could be more efficient
than what I am doing with a pure OO solution and reflection, depends
on how good the reflection method.invoke, field.get and field.set are
realized by the target platform.
Message has been deleted

Douglas Miles

unread,
Jan 22, 2016, 6:27:07 AM1/22/16
to Jan Burse, SWI-Prolog, Miloslav Raus
On Fri, Jan 22, 2016 at 1:59 AM, Jan Burse <burs...@gmail.com> wrote:
Looks like on the fly code generation is involved, here is an example:

    https://github.com/logicmoo/swicli/blob/master/c/Swicli.Library/PInvokeMetaObject.cs#L414-L455

Otherwise delegates wouldbn't work if SWI has only function pointer registration.
 

But still difficult for me to follow the flow, there are also competing register
entry points, such as libpl.PL_register_foreign_in_module and PlEngine.RegisterForeign.
Last but not least class names seem to be case insensitive, what the file names
on disk consider, hurts my eyes ... Brrr

PlEngine.RegisterForeign eventually leads back to  libpl.PL_register_foreign_in_module  with is the C interface.   There is actually was no code in libpl.*  as it's a FFI Facade for use by C# code of PlEngine and PlTermV (term_t)



SWI as far as when I last checked actually only has a "function pointer registration" system. However there are certain expectations of the methods you place at that pointer.   But  you have to generate a C callable trampolines (then "pin" it from Mono/.Net's  garbage collector )  It surprisingly works.  Mainly because the application binary interface for Mono/.Net  had to be savvy enough to be able to write callbacks. 

However in NondetContextHandle I just go straight for the libpl.PL_register_foreign_in_module mainly for debugging. Since creating nondeterministic functions in C# was initially was harrowing.
 
Uwe Lesta did something that was rather mind blowing to me when he  created Streams in C# and registered them into SWIPL.    When swipl writes to a IOSTREAM it is writing to a C# delegate,    in which I used to make those call back to prolog predicates until JanW created prolog_streams a few months ago.


Assuming now that the solution is based on on the fly code generation, my
claim here is still, that if SWI would already provide a delegate interface, this
would not be necessary. Possibly allowing CLI like interfaces also to C++
with a more minimal RTTI (Runtime Type Information), that doesn't
allow on the fly code generation.

Marshalling pointers and GC and everything else.. it'd end up being at best being only as good as libffi and it would be still do less than what is needed to do fun things..   (For instance in swicli someone can mix sun/oracle java classes with C++ code and with F# .. passing these objects between and allowing each other to get/set each other's fields while calling each other's methods and know GC is managing C++ as well.   The java classes don't know that the the classes they use are written in F# or prolog.
 

On the other hand on the fly code generation, could be more efficient
than what I am doing with a pure OO solution and reflection, depends
on how good the reflection method.invoke, field.get and field.set are
realized by the target platform.

Dunno, I prefer using reflection.  My first inclination was to call a cli_call/4 instead of the cli_intern_method/4 

For example, a here is a prolog file that mixes at least 3 different codebases to make robot run around in second life all using the reflection.



 

Am Freitag, 22. Januar 2016 02:54:07 UTC+1 schrieb Douglas Miles:
Reply all
Reply to author
Forward
0 new messages