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

Meta-interpreters in Prolog

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

elec.pl=


% adapted from
% Computational Intelligence:
% a logical approach. 

% lit(L) is true if light L is lit.
lit(L) :-
   light(L) ,
   ok(L) ,
   live(L).

% live(W) is true if W is live (i.e., current
% will flow through it if grounded)
live(outside).
live(W) :-
   connectedto(W,W1) ,
   live(W1).

% connectedto(W0,W1) is true if W0 is
% connnected to W1 such that current will
% flow from W1 to W0.

connectedto(l1,w0).
connectedto(w0,w1) :- up(s2).
connectedto(w0,w2) :- down(s2).
connectedto(w1,w3) :- up(s1).
connectedto(w2,w3) :- down(s1).
connectedto(l2,w4).
connectedto(w4,w3) :- up(s3).
connectedto(p1,w3).
connectedto(w3,w5) :- ok(cb1).
connectedto(p2,w6).
connectedto(w6,w5) :- ok(cb2).
connectedto(w5,outside).

% light(L) is true if L is a light
light(l1).
light(l2).

% up(S) is true if switch S is up
% down(S) is true if switch S is down
up(s2).
up(s3).
down(s1).

% ok(G) is true if G is working
% cb= circuit breaker
ok(l1).
ok(l2).
ok(cb1).
ok(cb2).

demos.pl=


% demos.pl

% handle the generic demo stuff

% run the demo predicate, saving output
demos(F) :-
         sformat(Out,'~w.out',F),
	 write(Out),nl,
	 tell(Out),
	 format('% output from ~w.pl\n',F), 
         % never fail 
	 ignore(demo),
	 told.

% run through all the demo1's
demo :- demo1,fail.
demo.

prove1.pl=


% prove1.pl

% simple meta-interpreter for prolog,
% written in prolog of course
:- [demos, star,elec].

% new main demo driver- demof
demof :- demos(prove1).

% demos hooks into demo1
demo1 :- nl, write('prolog: '),
	prolog(live(X)),
	format(' ~w',X).
demo1 :- nl, write('prove : '),
	 prove(live(X)),
	 format(' ~w',X).
demo1 :- nl, write('delta :  '),
     1000*prolog(live(_))/prove(live(_)).

% just call raw prolog
prolog(X) :- X.

% the "clause/2" predicate lets prolog
% access the definitions of asserted
% clauses. clause(head,body) ==> looks
% it up in the current rule
% clause(fact,X) ==> X = true

% cuts are needed cause the last clause
% is a "do everthing that is not the
% above". bad cuts, bad.

% base case
prove(true)  :- !.

% negation
prove(\+ X)  :- !,
	\+ prove(X).

% disjunction
% warning- note the brackets
% around the disjunction
prove((A;B)) :- !,
	(prove(A)
        ; prove(B)).

% conjunction
prove((A,B)) :- !,
	prove(A),
	prove(B).

prove(A) :-
	clause(A,B),
	prove(B).


Which generates prove1.out=


% output from prove1.pl

prolog:  outside w2 l2 w4 p1 w3 p2 w6 w5
prove :  outside w2 l2 w4 p1 w3 p2 w6 w5
delta :  0.111111 = [prolog(live(A))] 
                    / 
                    [prove(live(N))]

star.pl=


% star.pl

% stuff to time goals

:- ensure_loaded(format).

% compare runtimes of X and Y
N*X/Y :- !, % cut needed to we dont fall 
	    % into the next clause
	% cputime: swi function
	% to grab time (in secs). 
	Start is cputime,
	times(N,X),
	Mid is cputime,
	times(N,Y),
	End is cputime,
	Ratio is (Mid - Start)/(End - Mid),
	format('~p = [~P] / [~13P]',
	       [Ratio, X,Y]).

% repeat some goal N times, show how long
% it takes to run (using the built in 'time'
% predicate).
N*X :- time(times(N,X)).

% failure drive loop to repeat N times
times(N,X) :- between(1,N,_), X, fail.
times(_,_).

preprove.pl=


% preprove.pl

% pre-processer so we don't need
% those darn cuts in prove

% once(X) :- X,!.
preprove(X,Y) :- 
	once(preprove1(X,Y)).

% standard top-down parsing trick #1
% always check for the var case on top
preprove1(X, call(X))    :- var(X).

% standard top-down parsing trick #2
% sub-goals call the once-ed head
preprove1((X0,Y0),(X,Y)) :-
	preprove(X0,X),
	preprove(Y0,Y).
preprove1((X0;Y0),(X;Y)) :-
	preprove(X0,X),
	preprove(Y0,Y).
preprove1(\+ X0, \+ X)   :-
	preProve(X0,X).
preprove1(X,  call(X))   :-
	% swi-specific- slow!
	% should only ever call once!
	predicate_property(X,Y),
	(Y = builtin_in
        ; Y = imported_from(system)).
preprove1(X,  prove(X)).

term_expansion(+ X,X).
term_expansion((+ X :- Y0),(X :- Y)) :-
	preprove(Y0,Y).

dprove.pl=


% dprove.pl

% depth-first iterative deepenning
% pre-processor using a cut-less prove

:- [demos, star,preprove,elecplus].

demof :- demos(dprove).

demo1 :- listing(lit).
demo1 :- nl,
	 R=10000,
	 [elec],
	 Start1 is cputime,
	 R*(once(prolog(live(w5)))),
	 Stop1 is cputime,
	 [elecplus],
	 Start2 is cputime,	 
	 R*(once(dprove(live(w5),_))),
	 Stop2 is cputime,
	 Ratio is (Stop2 - Start2)
                  /(Stop1 - Start1),
	 format('interpreted / raw = ~w\n',
	          [Ratio]).

% just call raw prolog
prolog(X) :- X.

% shovel predicate.
% buries the real call inside a succincy
% high-level driver
dprove(X) :- dprove(X,_).

dprove(X,MaxDepth) :-
	between(1,10,MaxDepth),
	prove(prove(X),MaxDepth).

% observe the beauty of unique functors,
% possible after a one-time pre-processor
prove(true,     _).
prove(\+ X,     D) :- \+ prove(X,D).
prove((A;B),    D) :- prove(A,D); prove(B,D).
prove((A,B),    D) :- prove(A,D), prove(B,D).
prove(call(A),  _) :- A.
prove(prove(A),D0) :-
	D0 > 0,
	D is D0 - 1,
	clause(A,B),
	prove(B,D).

% odd tales of DFID
% repeats old searches
% B = xtra effort
% 2 = 4
% 3 = 2.25
% 4 = 1.77778
% 5 = 1.5625
% 6 = 1.44
% 7 = 1.36111
% 8 = 1.30612
% 9 = 1.26563
% 10 =1.23457
% with high branching factors, out-performs
% other searchers. if solution found, will be
% the shortest solution. if no solution found,
% will search on VERY deeply, not using
% much memory. so it will in a space effecient
% manner, search and search and search... .
% Hence, the call to once above.

Which generates dprove.out=


% output from dprove.pl

lit(A) :-
	prove(light(A)),
	prove(ok(A)),
	prove(live(A)).

interpreted / raw = 9.33333


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.