Visar inlägg med etikett MPS. Visa alla inlägg
Visar inlägg med etikett MPS. Visa alla inlägg

2008-10-16

Handling defrules in MPS, executing the RHS

I've been rewriting the deftemplate code for MPS more or less from scratch... but I'll have to talk about that some other time. It's high time to focus on the defrule macro(s). I'll break this up into several posts and I'll start with the function for executing the RHS.

The MPS syntax (a subset of CLIPS') for defrule looks like this:

  defrule-construct
::= (defrule rule-name
conditional-element*
=>
expression*)

conditional-element
::= template-pattern-CE ¦ assigned-pattern-CE ¦
not-CE ¦ and-CE ¦ or-CE ¦ test-CE ¦
exists-CE ¦ forall-CE

assigned-pattern-CE
::= single-field-variable <- template-pattern-CE

not-CE ::= (not conditional-element)
and-CE ::= (and conditional-element+)
or-CE ::= (or conditional-element+)
test-CE ::= (test function-call)
exists-CE ::= (exists conditional-element+)
forall-CE ::= (forall conditional-element
conditional-element+)

template-pattern-CE
::= (deftemplate-name single-field-LHS-slot*)

single-field-LHS-slot
::= (slot-name constraint)

constraint ::= ? connected-constraint


connected-constraint
::= single-constraint ¦
single-constraint & connected-constraint
single-constraint ¦ connected-constraint

single-constraint
::= term ¦ ~term

term ::= constant ¦ single-field-variable ¦
:function-call ¦ =function-call

single-field-variable
::= ?variable-symbol
I'm quite far from having all of the above supported, but I've got enough to show how the function that executes the RHS of a rule works.

The defrule macro works by expanding into a series of macro calls which handle more and more specific cases in the processing. The macro itself is quite simple
(defmacro defrule (name &body body)
(let ((rhs (cdr (member '=> body)))
(lhs (ldiff body (member '=> body))))
`(progn
(compile-lhs ,name ,@lhs)
(compile-rhs ,name ,@rhs))))
As you can see, it expands into two other macro-calls: compile-lhs and compile-rhs, where the first parses the conditional-elements and, in the process, creates two symbol-tables (fact-bindings and variable-bindings) with all of the variables it can find.

The second macro handles the RHS and looks like this:
(defmacro compile-rhs (name &body rhs)
(when (null rhs)
(setf rhs '(t)))
`(defun ,(make-sym "RHS/" name) (activation)
(let* ((token (activation-token activation))
,@(mapcar #'make-fact-binding (reverse fact-bindings))
,@(mapcar #'make-variable-binding (reverse variable-bindings)))
,@rhs)))
So, if we evaluate this:
MPS> (defrule foobar
?foo <- (foo (bar ?bar) (baz 1))
=>
(format t "~%~A ~A" ?foo ?bar))
it expands into this (among other things):
(DEFUN RHS/FOOBAR (ACTIVATION)
(LET* ((TOKEN (ACTIVATION-TOKEN ACTIVATION))
(?FOO (NTH 0 TOKEN))
(?BAR (DEFTEMPLATE/FOO-BAR ?FOO)))
(FORMAT T "~%~A ~A" ?FOO ?BAR)))
Most of the work is with figuring out how to assign values to each of the variables. I'm using a simple list as the structure for the tokens. WMEs (fact objects) are added in the order they appear in the list of conditional elements. Once all of the WMEs are bound, all of the variable-bindings are bound by using the automatically constructed accessor methods for those structs.

The actions in the RHS are simply spliced into the let* form at macro-expansion time which completes the function definition. It is then evaluated and stored with the rule's production node. Later, when that production node is left-activated, it creates an activation (with the WMEs and some additional meta-data like timestamps and such) and places it in the conflict-set. If that activation ever triggers a rule, it is passed as an argument to the RHS function.

Since I haven't got enough of "the rest" of MPS in place. We're going to have to mock an activation and call the function directly to see whether or not it works.
MPS> (rhs/foobar (make-activation :token (list (foo (bar 1) (baz 1)))))
#S(DEFTEMPLATE/FOO :BAR 1 :BAZ 1) 1
NIL
MPS>
There's really not much more to say about the RHS so I'll stop here. The LHS is a bit more complicated and I hope that I can show some of that code soon.

2008-08-23

MPS inference engine, the rest of the implementation

In the last post I mentioned a few of the design choices I've made for the Rete Network implementation. The rest of the engine is quite straight forward and simple. There's really not much to talk about but I'll show some code anyway ;-).

Another thing though, and a bit more interesting really, is that I have been thinking about whether or not I should try to stay true to CLIPS' behaviour and functionality in the misc engine functions as well.

For example, the agenda function currently returns a list of all activations on the agenda and CLIPS prints them but returns no value. Similarly there's facts which behaves like get-fact-list instead. Used at the REPL there's little difference in what the user sees but the reason I've made them different is because then I can write other functions on top of them.

Ok. As promised, some code. Here is the run function (which uses agenda):

|(defun run (&optional (limit -1))
| (do* ((curr-agenda (agenda) (agenda))
| (execution-count 0 (+ execution-count 1))
| (limit limit (- limit 1)))
| ((or (eq limit 0)
| (= (length curr-agenda) 0)) execution-count)
| (let* ((activation (first curr-agenda))
| (rhs-func (make-sym "RHS-" (string (activation-rule activation))))
| (prod-mem (make-sym "PRODUCTION-" (string (activation-rule activation)) "-MEMORY")))
| (funcall rhs-func activation)
| (store '- activation prod-mem))))
and here is the assert function (I'm shadowing the built-in assert function, still accessible as cl:assert though):
|(defun assert (&rest facts)
| (incf timestamp)
| (dolist (fact facts)
| (store '+ fact 'working-memory)
| (mapcar #'(lambda (node) (funcall node '+ fact timestamp))
| (gethash (type-of fact) (gethash 'root rete-network)))))
I hope that they are at least somewhat readable to others.

I've now finished the functions that make up the inference engine implementation. And it works... as long as you manually divide your program into alpha, beta and production nodes and connect them properly in the Rete Network ;-)

2008-08-15

MPS inference engine, the Rete Network implementation

It's difficult to talk about the MPS defrule macro and the code it expands to without first explaining the environment in which it is meant to run. So I'll try to explain and describe my current thoughts and ideas that make up the design of the MPS inference engine in this and following posts.

The engine is made up of some I/O functions (assert and retract), the Rete Network, a Conflict Resolver and an Execution Engine. The Rete Network is the most central part of the whole thing so I'll start there.

It is basically implemented within a hash-table. This is the simplest possible representation of a Rete Network that I can think of. There are, of course, a few helper functions to abstract away some of the book keeping details of this design choice. During rule compilation there are functions for adding a node/memory and connecting nodes/memories with each other and at run time there are functions to propagate facts/tokens, access contents of and store facts/tokens in memory.

A processing node (for example an alpha node) is implemented as a function and is stored in the hash-table as well. A very simple LHS construct like:

|(defrule foo
| (bar (baz ?baz&:(> ?baz 10)))
| =>)
would be represented in the Rete Network by the following function:
|(defun bar-baz->-10 (key fact timestamp)
| (when (> (deftemplate/bar-baz fact) 10)
| (store key fact 'bar-baz->-10-memory)
| (propagate key fact timestamp 'bar-baz->-10)))
A join node is represented by two functions (one for left and one for right activation) and is slightly more complex (but not much). If we change the LHS to:
|(defrule foo
| (bar-1 (baz ?baz))
| (bar-2 (baz ?baz))
| =>)
we would have to create a join node for joining facts on the ?baz variable. It would look something like this:
|(let ((left-memory  'bind-bar-1-memory)
| (right-memory 'bind-bar-2-memory))
| (defun join-bar-1-baz-and-bar-2-baz-left (key token timestamp)
| (dolist (fact (contents-of right-memory))
| (when (eq (bar-1-baz (nth 0 token))
| (bar-2-baz fact))
| (store key (append token (list fact)) 'join-bar-1-baz-and-bar-2-baz-memory)
| (propagate key (append token (list fact)) timestamp 'join-bar-1-baz-and-bar-2-baz))))
|
| (defun join-bar-1-baz-and-bar-2-baz-right (key fact timestamp)
| (dolist (token (contents-of left-memory))
| (when (eq (bar-1-baz (nth 0 token))
| (bar-2-baz fact))
| (store key (append token (list fact)) 'join-bar-1-baz-and-bar-2-baz-memory)
| (propagate key (append token (list fact)) timestamp 'join-bar-1-baz-and-bar-2-baz)))))
As you can see variables are expanded into "positions" everywhere in the functions. Variables are, however, available and bound in the execution context of the production node's RHS function.

There are some more bits and pieces that are good to know. The root node, for example, is a hash-table. Each deftemplate-type is a key and the value contains a list of alpha nodes.

Compilation consists of (apart from expanding the rule's LHS into a number of functions) a series of calls to add-to-root and connect-nodes. Since each node is responsible for propagating as well as storing facts/tokens in memory we can connect the processing nodes to each other directly. The example above would be compiled with:
|(add-to-root 'bar-1 #'bind-bar-1) ; This might not be necessary! We should
|(add-to-root 'bar-2 #'bind-bar-2) ; be able to connect directly to the join.
|(connect-nodes 'bind-bar-1 #'join-bar-1-baz-and-bar-2-baz-left)
|(connect-nodes 'bind-bar-2 #'join-bar-1-baz-and-bar-2-baz-right)
|(connect-nodes 'join-bar-1-baz-and-bar-2-baz #'production-foo)
This is all theory, though. I don't actually have all of the defrule macro in place so the final version might very well expand into something different. But I hope this conveys the general idea of the Rete Network implementation.

2008-08-11

Handling deftemplates in MPS

There are three parts to my MPS (Minimal Production System) experiment, the "engine" itself and the deftemplate and defrule macros. So far, I've spent most of my time on the deftemplate macro. It turned out to be a bit trickier than I thought to implement. Mostly because I was stuck thinking about too complex macro expansions (which I never got to work).

Here is the syntax as BNF (well, sort of[1]):

|  deftemplate-construct
| ::= (deftemplate deftemplate-name
| [comment]
| single-slot-definition*)
|
| single-slot-definition
| ::= (slot slot-name [default-attribute])
|
| default-attribute
| ::= (default ?NONE | expression) |
| (default-dynamic expression)
It is a subset of CLIPS' deftemplate syntax. There are no multislots and no constraint-attributes for slots (types, ranges and such). But, apart from that, it is more or less the same[2]. And here's how it works:
|; SLIME 2007-03-14
|;;;; Compile file / [...] /mps. ...
|CL-USER> (in-package :mps)
|#[Package "MPS"]
|MPS> (deftemplate foo
| (slot a-slot)
| (slot a-default-slot (default 1))
| (slot required-slot (default ?NONE)))
|FOO
|MPS> (foo)
|
|The slot: REQUIRED-SLOT in deftemplate: FOO requires an explicit value.
| [Condition of type SIMPLE-ERROR]
|
|Restarts:
| 0: [ABORT] Return to SLIME's top level.
| 1: [ABORT-BREAK] Reset this process
| 2: [ABORT] Kill this process
|
|Invoking restart: Return to SLIME's top level.
|; Evaluation aborted
|MPS> (foo (required-slot 1))
|#S(DEFTEMPLATE/FOO :A-SLOT NIL :A-DEFAULT-SLOT 1 :REQUIRED-SLOT 1)
|MPS> (deftemplate bar
| (slot default-gensym (default (gensym)))
| (slot dynamic-gensym (default-dynamic (gensym))))
|BAR
|MPS> (bar)
|#S(DEFTEMPLATE/BAR :DEFAULT-GENSYM #:G31 :DYNAMIC-GENSYM #:G40)
|MPS> (bar)
|#S(DEFTEMPLATE/BAR :DEFAULT-GENSYM #:G31 :DYNAMIC-GENSYM #:G41)
|MPS>
The macro expands into a defstruct (deftemplate/foo) and another defmacro (foo) that is used as a constructor for the template. The reason it is a macro and not a regular function is because a function's arguments are evaluated whilst a macro's is not. And since there's no function named a-slot or a-default-slot etc. So we'd be thrown into the debugger if we tried to evaluate something like (foo (a-slot 1)).

Here's the macroexpansion of a simple template:
|MPS> (pprint (macroexpand-1 '(deftemplate foo
| (slot a)
| (slot b (default 1)))))
|
|(PROGN (DEFSTRUCT DEFTEMPLATE/FOO "" (A NIL) (B 1))
| (DEFMACRO FOO (&REST SLOTS)
| ""
| (CALL-DEFSTRUCT-CONSTRUCTOR 'DEFTEMPLATE/FOO SLOTS)))
|; No value
|MPS>
Most of the code is spent checking that the template follows the syntax described in the BNF. The expansion itself is rather simple, almost trivial (it is the last progn below).
|(defmacro deftemplate (deftemplate-name &body body)
| "
| The deftemplate construct is used to create a template which can then
| be used by non-ordered facts to access fields of the fact by name.
|
| Examples:
| (deftemplate object
| (slot id (default-dynamic (gensym)))
| (slot name (default ?NONE)) ; Makes name a required field
| (slot age))
| "
|
| (macrolet ((signal-deftemplate-error (msg &rest args)
| `(error (concatenate 'string "~&The deftemplate ~A contains at least one invalid slot-definition: ~S." ,msg)
| ,@args)))
| (let ((comment "")
| (defstruct-name (intern (concatenate 'string "DEFTEMPLATE/" (string deftemplate-name))))
| (defstruct-slots '()))
|
| ;; Extract the documentation string
| (when (stringp (car body))
| (setf comment (car body))
| (setf body (cdr body)))
|
| ;; Check syntax and extract slot-specifiers
| (dolist (slot body)
| (let* ((slot-name (cadr slot))
| (curr-defstruct-slot `(,slot-name nil)))
| (unless (eq (car slot) 'slot)
| (signal-deftemplate-error "~&Expected SLOT instead of ~A."
| deftemplate-name slot (car slot)))
|
| (when (> (length slot) 2)
| (dolist (default-attribute (cddr slot))
| (unless (consp default-attribute)
| (signal-deftemplate-error "~&Expected (default ?NONE|expression) or (default-dynamic expression) instead of ~A."
| deftemplate-name slot default-attribute))
| (unless (or (eq (car default-attribute) 'default)
| (eq (car default-attribute) 'default-dynamic))
| (signal-deftemplate-error "~&Expected DEFAULT or DEFAULT-DYNAMIC instead of: ~A."
| deftemplate-name slot (car default-attribute)))
| (if (eq (car default-attribute) 'default)
| (if (eq (cadr default-attribute) '?NONE)
| (setf curr-defstruct-slot `(,slot-name (required ',slot-name ',deftemplate-name)))
| (setf curr-defstruct-slot `(,slot-name ',(eval (cadr default-attribute)))))
| (setf curr-defstruct-slot `(,slot-name ,(cadr default-attribute))))))
|
| (setf defstruct-slots (append defstruct-slots (list curr-defstruct-slot)))))
|
| `(progn
| (defstruct ,defstruct-name
| ,comment
| ,@defstruct-slots)
|
| (defmacro ,deftemplate-name (&rest slots)
| ,comment
| (call-defstruct-constructor ',defstruct-name slots))))))
and here are the functions used as helpers:
|(defun required (slot-name deftemplate-name)
| (error "~&The slot: ~A in deftemplate: ~A requires an explicit value." slot-name deftemplate-name))
|
|(defun as-keyword (sym)
| (intern (string-upcase sym) :keyword))
|
|(defun call-defstruct-constructor (defstruct-name &rest slots)
| (let ((constructor (intern (concatenate 'string "MAKE-" (string defstruct-name)))))
| (apply constructor (mapcan #'(lambda (slot)
| `(,(as-keyword (car slot)) ,(cadr slot)))
| (car slots)))))
I should probably try to write a macro to abstract away all those (intern (concatenate 'string ...)) calls but otherwise, that's about it for deftemplate. Next up is getting all of the defrule construct working (which feels like a much tougher task).

[1] I hate that I still haven't found a good way of sharing code using Blogger. Tips and pointers are very welcome!

[2] The default and default-dynamic attributes in CLIPS take a variable number of expressions (at least according to the BNF found in the CLIPS Basic Programming Guide, Appendix H). I assume it assigns the value of the last as the default but I haven't tried. Anyway, if you want to evaluate several expressions in that place you're going to have to wrap it explicitly in a progn (effectively making it one expression).

2008-08-02

A Minimal Production System

I've been experimenting a bit with bits and pieces of a production system in Common Lisp for a few days now. It all started as a fun exercise in Common Lisp macrology (the idea was to convert CLIPS syntax into executable Common Lisp code) but since things have fallen into place so neatly. I thought maybe it would be worth implementing parts of CLIPS syntax and functionality. So now, the only question is: which parts to implement?

I'm not going to do anything about data types and built-in functions. I'll add support for ?variables but that's about it (no multifields and no globals) and as far as constructs go I'll manage with defrule and deftemplate (no implied/ordered facts). If it doesn't turn out to be too difficult I'll try to include connected constraints in defrule but I won't bother with slot constraints in deftemplates (types and such). I'm hoping to include all CEs but it depends on how hairy it gets.

So. What have I missed? Is there something unnecessary on the list?

[Update 2008-08-03]: Hm. I guess I forgot about a bunch of engine commands. So here goes. Assert and retract seem stupid to leave out, as does run. I'll probably be annoyed not to have facts so I guess that's in as well. Load, clear, reset and agenda feel necessary but I think I'll only work with one conflict resolution strategy (depth) though.