Okay, I have found the missing definition (code was split by page break), and found the type error:

   type Subst = [(Var,Term)]

should be:

   type Subst = [(Vname,Term)]

And have written a simple implementation of unify from a description of the algorithm. I was wondering if anyone has any comments on my implementation of unify? For example can the algorithm be simplified from my nieve attempt? Most importantly is it correct?

   type Subst = [(Vname,Term)]
   data Term = Func Fname [Term] | Var Vname deriving (Eq,Show)
   type Fname = String
   data Vname = Name String | Auto Integer deriving (Eq,Show)

   unify :: Subst -> (Term,Term) -> [Subst]
   unify s (t,u) | t == u = [s]
   unify s (Var x,t) = [(x,t):s] -- no occurs check
   unify s (t,Var x) = [(x,t):s] -- no occurs check
   unify s (Func f ts,Func g us)
           | f == g = unify' s ts us
           | otherwise = []
unify' :: Subst -> [Term] -> [Term] -> [Subst]
   unify' s [] [] = [s]
   unify' s (t0:ts) (u0:us) = case unify s (t0,u0) of
           s@(_:_) -> unify' (concat s) ts us
           _ -> []

Keean.

Keean Schupke wrote:

Does anyone know if the source code for the embedded prolog (by Silvija Seres & Michael Spivey) is available for download from anywhere? I have read the paper and found some of the types are wrong, some critical definitions are missing, and the definition of unify is missing.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to