EECE 571F= Domain-Specific Languages  
  
This is a page from yet
another great ECE, UBC subject.
[ Home | Assignments | Lectures |
DSL rules | Articles | Resources ]

Lectures (5)

Lectures:
Old: 1 | 2 | 3 | 4 | 5
New: DCGnums | Parsing | Meta-prolog | Faster1 | Faster2 | Rand-nums
Not done: Abduction | Stochastic abs

Rule-based Programming

Rules: for computation in response to pre-conditions.
  • Not for rigidly pre-defined schemes
  • Good for prototyping: throw all ideas into rules as you stumble across them

UML 'states' can be loosely modelled as rule 'groups':

  • States are small, and rule groups are for conceptually large units.
  • Rule-based languages give some control over when groups are entered and exited.
  • A group is a place to stuff a grab bag of ideas.
  • Within a group, a rule interpreter looks for rules that can be fired, fires them, then looks again.
  • Within a group, order emerges, is not pre-determined.

State transition diagrams = details of jumping around a program.

Rules= looser description of program execution.

    
       complete    consistent     determinate
STD    yes         yes            yes
Rules  maybe       maybe          maybe

Rules operate on a working memory:

  • Working memory contents trigger rules.
  • Triggered rules update working memory.
  • Repeat till end of time

        trigger 
    ______>>__________
   /                  \
WORKING                RULE
MEMORY                 BASE
   \______<<___________/
        update
Rules = pairs
  • If guard happy,
  • Then do action
  • Go find another rule with a happy guard.
Rule interpreters work via a match-select-act loop:
  • Match: find the rules in the current group whose guards are satisfied by the current contents of working memory.
  • Select: pick one using a conflict resolution strategy (discussed below).
  • Act: fire the picked rule and maybe modify working memory
  • And repeat till nothing can be matched.

Difference between expert and novice performance:

  • Novices stuff up their working memory with too many goals.
  • Experts have compiled their knowledge into rules that know what to do next.
      Less clutter in working memory.

Some conflict resolution strategies:

  • Refraction= don't do the same thing twice.
    • Whenever we use a rule, we assert a refraction/2 fact to note we have used it.
    • When we test a condition, we check that we have not used this before (i.e. \+ refraction).
  • Priority ordering= rules listed first have higher priority that those listed later
    • Prolog matches top-down, so we get that for free.
  • Salience ordering= rules with a higher numeric priority have higher priority that those with smaller priorities.
  • Recency: focus on recently generated assertions rather than older ones:
    • Neat exception control mechanism- exceptions are asserted and the exception handler rules instantly wake up to handle it.
  • Specificity: Prefer more specific rules (that have more condition tests) over more general rules (that have less conditions).

Example of Rule-Based Programming

Robbie the Robot, bagging groceries.

Rule groups:

  • Check order: look for anything that needs to be fixed in the order/
      E.g.if they bought potato chips but no Pepsi, they'll die of thirst
  • Bag large items
  • Bag medium sized items
  • Bag small items
Sounds silly but..
  • The worlds first commercial expert system (XCON, 1980) worked this way: saved DEC M-M per year when their top designers no longer had to manually check new orders.
  • And other applications found this technology to be cost effective; e.g. PIGE, 1988 (described below).
The check order rules are:

b1 if   the step is check order
    there is a bag of potato chips
    there is no soft drink bottle
then add one bottle of pepsi to the order

b2 if   the step is check order
then    discontinue the check-order step 
    start the bag large items step

B1 is more specific than B2, so it gets fired first. Afterwards, B2 is fired to jump groups.

Here are the bag large item rules


b3 if   the step is bag large items
    there is a large item to be bagged
    there is a large bottle to be bagged
    there is a bag with < 6 large items
then    put the bottle in the bag

b4      if there step is bag large items
    there is a large item to be bagged
    there is a bag with < 6 large items
then    put the large item in the bag

b5      if there step is bag large items
    there is a large item to be bagged
then    start a fresh bag

b6 if   the step is bag large items
then    discontinue the bag large step 
    start the bag medium items step
B3 patches a hole in B4: bottles should be bagged first cause they are heavy. Again, B3 fires first because it is more specific.

B5 is a natural rule: if we can't do anything more specific and we still have large items to bag, then start a new bag and place the large items in it.

B6 is the most general bag large items rule so it is fired last to jump us to bag medium items.

Here are the bag medium item rules:


b8 if   the step is bag medium items
    there is a medium item to be bagged
    there is an empty bag or a bag with medium items
then    put the medium item in the bag

b9 if   the step is bag medium items
    there is a medium item to be bagged
then    start a fresh bag

b10 if   the step is bag medium items
then    discontinue the bag medium step 
    start the bag small items step
These are very natural rules: medium items should bagged together (B8) and if we run out of bags, start a new one (B9). Finally, when all the medium bagging operations are done, jump to bagging small items.

Here are the bag small items rules:


b11 if  the step is bag small items
    there is a small item
    there is a bag that is not yet full
    the bag does not contain bottles
then    put the small item in the bag

b12 if  the step is bag small items
    there is a small item
    there is a bag that is not yet full
then    put the small item in the bag
B11 says we can slip small items into non-full bags along as bottles can't crush them. Otherwise, in B12, for bags without bottles, we can slip in the small items. Note for rule interpreters that support specificity, B11's longer condition (which mentions bottles) effectively blocks B12 from firing.
Implementing Rule-Based Programming We need to pull apart


start/1 
if    year(Y) and Y >= 1900 and Y < 2001
then  say(modern(Y)) and goto(century20).

into


gaurd(start, 1, [A]) :-
    group(start),
    year(A)and A>=1900 and A<2001,
    \+refraction(start, 1, [A]).

action(start, 1, [A]) :-
    assert(refraction(start, 1, [A])),
    say(modern(A))and goto(century20).

One thing we need to do is find the variables that are passed from the guard to the action. Our old friend runiv/2 will suffice:


vars(Term,All) :-
    setof(One,aVar(Term,One),All).

aVar(Term,V) :- runiv(Term,V), var(V).
runiv(X,X).
runiv(In, X) :-
    nonvar(In),
    In =.. [A,B|C],
    member(Y,[A,B|C]),
    runiv(Y,X).

So we only need to find all the vars in the IF and the THEN, then their set intersection:



sameVars([],_,[]).
sameVars([H|T],L,[H|Rest]) :-
    member(X,L),
    H == X,!,
    sameVars(T,L,Rest).
sameVars([_|T],L,Rest) :-
    sameVars(T,L,Rest).

The rest is straight forward.


% rules.pl

demo :- tell('rules.out'),ignore(demo1),told.

demo1 :- 
    listing(gaurd),
    listing(action),
    nl,
    nl,
    think,
    listing(refraction).

% hooks into the Prolog compiler- some new keywords
:- op(1005,xfx,if).
:- op(1004,xfx,then).
:- op(1003,xfy,or).
:- op(1002,xfy,and).
:- op(1001,fy,not).

% control statements for assertions
:- dynamic group/1,refraction/3.
:- discontiguous gaurd/3, action/3.
:- index(refraction(1,1,0)).

% load time hook. convert X if Y then Z into
% "if" statements and "then" statements.
term_expansion(Group/Id if IF then THEN,
          [(gaurd(Group,Id,Shared) :-
                 group(Group),
                     IF,
                     \+ refraction(Group,Id,Shared))
          ,(action(Group,Id,Shared) :-
                 assert(refraction(Group,Id,Shared)), 
                     THEN)]) :-
    vars(IF,V1),
    vars(THEN,V2),
    sameVars(V1,V2,Shared).

% low-level utilities

sameVars([],_,[]).
sameVars([H|T],L,[H|Rest]) :-
    member(X,L),
    H == X,!,
    sameVars(T,L,Rest).
sameVars([_|T],L,Rest) :-
    sameVars(T,L,Rest).

vars(Term,All) :-
    setof(One,aVar(Term,One),All).

aVar(Term,V) :- runiv(Term,V), var(V).
runiv(X,X).
runiv(In, X) :-
    nonvar(In),
    In =.. [A,B|C],
    member(Y,[A,B|C]),
    runiv(Y,X).

start/1 
if    year(Y) and Y >= 1900 and Y < 2001
then  say(modern(Y)) and goto(century20).

start/2
if    year(Y) and Y < 1900 and Y >= 1800 
then  say(modern(Y)) and goto(century19).

start/3
if    year(Y) and Y >= 2001
then  say(postmodern(Y)) and goto(century21).

century21/1
if    month(M)
      and member(M,[5,6,7,8])
then  say(happySummer(M)).

% top level
think  :- say(thinking), reset, run, say(thought).
reset  :- retractall(refraction(_,_,_)), goto(start).

% match select act loop
run  :- match(Maybes),!, select(Maybes, One), act(One),run.
run.

match(Maybes) :-
    bagof(Group/Id/Shared,gaurd(Group,Id,Shared),Maybes).

select([X|_],X).

act(Group/Id/Shared) :-
    action(Group,Id,Shared).

% jump groups
goto(X) :-
    retractall(group(_)),
    asserta(group(X)).

% rule support code
X and Y   :- X,Y.
X or  Y   :- X;Y.
year(X)  :- get_time(A), convert_time(A,X,_,_,_,_,_,_).
say(X)   :- print(X),nl.

month(1).
month(6).
month(7).
month(12).

Which produces


gaurd(start, 1, [A]) :-
    group(start),
    year(A)and A>=1900 and A<2001,
    \+refraction(start, 1, [A]).
gaurd(start, 2, [A]) :-
    group(start),
    year(A)and A<1900 and A>=1800,
    \+refraction(start, 2, [A]).
gaurd(start, 3, [A]) :-
    group(start),
    year(A)and A>=2001,
    \+refraction(start, 3, [A]).
gaurd(century21, 1, [A]) :-
    group(century21),
    month(A)and member(A, [5, 6, 7, 8]),
    \+refraction(century21, 1, [A]).

action(start, 1, [A]) :-
    assert(refraction(start, 1, [A])),
    say(modern(A))and goto(century20).
action(start, 2, [A]) :-
    assert(refraction(start, 2, [A])),
    say(modern(A))and goto(century19).
action(start, 3, [A]) :-
    assert(refraction(start, 3, [A])),
    say(postmodern(A))and goto(century21).
action(century21, 1, [A]) :-
    assert(refraction(century21, 1, [A])),
    say(happySummer(A)).

thinking
postmodern(2001)
happySummer(6)
happySummer(7)
thought

refraction(start, 3, [2001]).
refraction(century21, 1, [6]).
refraction(century21, 1, [7]).


Not © Tim Menzies, 2001
Share and enjoy- information wants to be free.
But if you take anything from this site,
please credit tim@menzies.com.