home *** CD-ROM | disk | FTP | other *** search
/ ARM Club 3 / TheARMClub_PDCD3.iso / hensa / programming / hugs_1 / demos_prolog_hs_AndrrEngne < prev    next >
Encoding:
Text File  |  1996-08-12  |  4.2 KB  |  100 lines

  1. {-
  2. By Donald A. Smith, December 22, 1994, based on Mark Jones' PureEngine.
  3.  
  4. This inference engine implements a variation of the Andorra Principle for
  5. logic programming. (See references at the end of this file.) The basic
  6. idea is that instead of always selecting the first goal in the current
  7. list of goals, select a relatively deterministic goal.
  8.  
  9. For each goal g in the list of goals, calculate the resolvents that would
  10. result from selecting g.  Then choose a g which results in the lowest
  11. number of resolvents.  If some g results in 0 resolvents then fail.
  12. (This would occur for a goal like:  ?- append(A,B,[1,2,3]),equals(1,2).)
  13. Prolog would not perform this optimization and would instead search
  14. and backtrack wastefully.  If some g results in a single resolvent
  15. (i.e., only a single clause matches) then that g will get selected;
  16. by selecting and resolving g, bindings are propagated sooner, and useless
  17. search can be avoided, since these bindings may prune away choices for
  18. other clauses.  For example: ?- append(A,B,[1,2,3]),B=[].
  19. -}
  20.  
  21. module AndorraEngine where
  22.  
  23. import Prolog
  24. import Subst
  25.  
  26. version = "Andorra Principle Interpreter (select deterministic goals first)"
  27.  
  28. solve   :: Database -> Int -> Subst -> [Term] -> [Subst]
  29. solve db = slv where
  30.    slv           :: Int -> Subst -> [Term] -> [Subst]
  31.    slv n s [] = [s]
  32.    slv n s goals =
  33.     let allResolvents = resolve_selecting_each_goal goals db n in
  34.       let (gs,gres) =  findMostDeterministic allResolvents in
  35.           concat [slv (n+1) (u**s) (map (app u) (tp++gs)) | (u,tp) <- gres]
  36.  
  37. resolve_selecting_each_goal::
  38.     [Term] -> Database -> Int -> [([Term],[(Subst,[Term])])]
  39. --  For each pair in the list that we return, the first element of the
  40. --  pair is the list of unresolved goals; the second element is the list
  41. --  of resolvents of the selected goal, where a resolvent is a pair
  42. --  consisting of a substitution and a list of new goals.
  43. resolve_selecting_each_goal goals db n = [(gs, gResolvents) |
  44.       (g,gs) <- delete goals, gResolvents = resolve db g n]
  45.  
  46. -- The unselected goals from above are not passed in.
  47. resolve :: Database -> Term -> Int -> [(Subst,[Term])]
  48. resolve db g n = [(u,tp) | (tm:-tp)<-renClauses db n g, u<-unify g tm]
  49. -- u is not yet applied to tp, since it is possible that g won't be selected.
  50. -- Note that unify could be nondeterministic.
  51.  
  52. findMostDeterministic:: [([Term],[(Subst,[Term])])] -> ([Term],[(Subst,[Term])])
  53. findMostDeterministic  allResolvents = minF comp allResolvents where
  54.    comp:: (a,[b]) -> (a,[b]) -> Bool
  55.    comp (_,gs1) (_,gs2) = (length gs1) < (length gs2)
  56. -- It seems to me that there is an opportunity for a clever compiler to
  57. -- optimize this code a lot. In particular, there should be no need to
  58. -- determine the total length of a goal list if it is known that
  59. -- there is a shorter goal list in allResolvents ... ?
  60.  
  61. delete ::  [a] -> [(a,[a])]
  62. delete l = d l [] where
  63.    d :: [a] -> [a] ->  [(a,[a])]
  64.    d [g] sofar = [ (g,sofar) ]
  65.    d (g:gs) sofar = (g,sofar++gs) : (d gs (g:sofar))
  66.  
  67. minF               :: (a -> a -> Bool) -> [a] -> a
  68. minF f (h:t) = m h t where
  69. --   m :: a -> [a] -> a
  70.      m sofar [] = sofar
  71.      m sofar (h:t) = if (f h sofar) then m h t else m sofar t
  72.  
  73. prove    :: Database -> [Term] -> [Subst]
  74. prove db  = solve db 1 nullSubst
  75.  
  76. {- An optimized, incremental version of the above interpreter would use
  77.   a data representation in which for each goal in "goals" we carry around
  78.   the list of resolvents.  After each resolution step we update the lists.
  79. -}
  80.  
  81. {- References
  82.  
  83.    Seif Haridi & Per Brand, "Andorra Prolog, an integration of Prolog
  84.    and committed choice languages" in Proceedings of FGCS 1988, ICOT,
  85.    Tokyo, 1988.
  86.  
  87.    Vitor Santos Costa, David H. D. Warren, and Rong Yang, "Two papers on
  88.    the Andorra-I engine and preprocessor", in Proceedings of the 8th
  89.    ICLP. MIT Press, 1991.
  90.  
  91.    Steve Gregory and Rong Yang, "Parallel Constraint Solving in
  92.    Andorra-I", in Proceedings of FGCS'92. ICOT, Tokyo, 1992.
  93.  
  94.    Sverker Janson and Seif Haridi, "Programming Paradigms of the Andorra
  95.    Kernel Language", in Proceedings of ILPS'91. MIT Press, 1991.
  96.  
  97.    Torkel Franzen, Seif Haridi, and Sverker Janson, "An Overview of the
  98.    Andorra Kernel Language", In LNAI (LNCS) 596, Springer-Verlag, 1992.
  99. -}
  100.