guile-user
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

forward chaining


From: Stefan Israelsson Tampe
Subject: forward chaining
Date: Fri, 22 May 2015 22:23:32 +0200

Hi guilers!

I was playing with guile log and the prolog theirin to introduce forward chaining building up databases and lookup tables. So let's go on to a nice examples in graph theory.

Consider the problem with a huge graph, but the graph consists of clusters and don't have 
much arrows going between the clusters. Also the number of clusters are not that large and the individual clusters are not that large. The task is to setup an effective system that calculates a maping from one node to the next globally if there is a chain linking them. So what you can do is to calculate a lookup table for the individual cluster and also a relational mapping of the cluster themslf. We also need to map the individual interface nodes.

The inteface of library(forward_chaining) is as follows. There is a directive set_trigger/1 that defines the name of the trigger function that will be calculated.  Then this atom will be used in consequent rules defining a forwars chaining indicated with =f> as an operator that is similart to :- ,  --> etc in prolog. Also the mappings will be effectively stored in lookup tables in dynamic predicates, so one need to declare those as well, the prelude is therefore,

:- use_module(library(forward_chaining)).

:- set_trigger(t).

:- dynamic(arrow/2).
:- dynamic(parent/2).
:- dynamic(parrow/2).
:- dynamic(interface/4).


Now for the rules,

arrow(X,Y),parent(X,XX),parent(Y,YY) =f>
   {XX==YY} -> parrow(X,Y) ; 
   (parrow(XX,YY),interface(X,Y,XX,YY)).

This rule will maintain databases arrow/2 of arrows introduced, parent/2 a database
 of cluster relations and as a conequence if the clusters are the same make a parrow/2 relation 
or parraw/2 and interface/4 relation. The parrow is goverend by the transitive law

parrow(X,Y),parrow(Y,X) =f> parrow(X,Z).

parrow(X,Y)      will tell if Y can be gotten from X inside the same cluster and
parrow(XX,YY) will tell if YY cluster can be gotten from the XX but not nessesary. (This is 
used to cut off branches later)


That''s the forward chaining part, we make some custom functions to add data to the database e.g.

set_arrow(X,Y)  :- fire(t,arrow(X,Y)).
set_parent(X,Y) :- fire(t,parent(X,Y)).

You issue these functions for each arrow relation and cluster relation in the system. And the databases will be setuped just fine through the triggering system inherent in forward chaining.

The meat
'x->y?'(X,Y) :-
  parent(X,XX),parent(Y,YY),  
  XX== YY -> parrow(X,Y) ; i(X,Y,XX,YY). 

this is plain backward chaining, not defining any databases. We just dispatch depending if the clusters are the same or not. If they are the same, it's a microsecond away in the lookup table of
parrow/2, else we dispatch to i. i is interesting, here it is:

i(X,Y,XX,YY) :-
    parrow(XX,YY),
    (
(interface(Z,W,XX,YY),parrow(X,Z),parrow(W,Y))  ; 
interface(Z,W,XX,ZZ),parrow(X,Z),i(W,Y,ZZ,YY)
    ).
Well XX must relate to YY aka parrow/2. But that is just a rough estimate, a hash value, if they are the same we must do more work. we first try to go to an interface node directly from XX to YY via interface Z,W. for all of those we try to match a parrow/2 lookup as it is defined whithin the same cluster but that may fail and then we try to jump to via an intermediate cluster.

An lookup table for the whole global system is expensive memory wize and you easy blow 
guile-log's limit of 10000 elements in the database. But the lookup tables for these systems are very hardly optimized for fast lookup. Now just doing the lookup tables for the individual clusters
will make it scalable for larger system then if these tricks where not used. I find this system is
a nice middle ground between creating gigantic lookup tables and do eveythng in searches that
can take quite some time.

have fun!!!

/Stefan


reply via email to

[Prev in Thread] Current Thread [Next in Thread]