pce_meta.pl -- Reflection support for XPCE
This module defines utilities to simplify reflexion support of XPCE, notably implementing non-deterministic logical relations on top of the deterministic XPCE methods.
- pce_to_method(+Spec, -Object) is semidet
- Object is the XPCE object described by Spec. Spec is one of
- send(Receiver, Selector)
- Receiver -> Selector
- Find a send-method on Receiver
- get(Receiver, Selector)
- <-(Receiver, Selector)
- Find a get-method on Receiver
- Receiver - Selector
- Find an instance variable (slot) on Receiver
- ClassName
- Find a class from its name
- isa_class(?Sub, ?Super)
- Succeeds if Sub is Super or below Super. Can be used with any instantiation. If class is instantiated the super-chain is followed.
- current_class(?Name, ?Class)
- Convert between name and class object. Insufficient instantation enumerates the classes.
- to_class_name(+AtomOrClass, -ClassName)
- Convert a name or class-object into a class name
- pce_library_class(?Name, ?Super, ?Comment, ?File)
- Examine the library index for defined classes.
- implements(?Class:atom, ?Method:atom) is nondet
- implements(?Class:atom, ?Method:atom, -MethodObj:object) is nondet
- True if Class implements the method. If class is a variable,
backtracking yields all classes
`What' may be wrapped in
self(What)
orroot(What)
. Usingself(What)
returns only those classes that have a non-inherited implementation of the method, while usingroot(What)
returns only those classes for which there is no super-class implementing the requested method. - pce_to_pl_type(+PceType, -PrologType)
- Convert an XPCE Type object to our type-checkers type-logic.
- type_accepts_function(+Type)
- Succeeds if Type accepts function arguments
- classify_class(+ClassName, -Classification) is det
- Classify an XPCE class. Defined classes are:
- built_in
file(File)
library(File)
user(File)
- user
- undefined
- implements(?Class:atom, ?Method:atom) is nondet
- implements(?Class:atom, ?Method:atom, -MethodObj:object) is nondet
- True if Class implements the method. If class is a variable,
backtracking yields all classes
`What' may be wrapped in
self(What)
orroot(What)
. Usingself(What)
returns only those classes that have a non-inherited implementation of the method, while usingroot(What)
returns only those classes for which there is no super-class implementing the requested method.