Unifcation and matching in Abelian groups

I've been studying equational unification. I decided to test my understanding of it by implementing unification and matching in Abelian groups. I am quite surprised by how little code it takes. Let me share it with you. John Test cases: 2x+y=3z 2x=x+y 64x-41y=a Code:
-- Unification and matching in Abelian groups -- John D. Ramsdell -- August 2009
module Main (main, test) where
import Data.Char (isSpace, isAlpha, isAlphaNum, isDigit) import Data.List (sort) import System.IO (isEOF)
-- Chapter 8, Section 5 of the Handbook of Automated Reasoning by -- Franz Baader and Wayne Snyder describes unification and matching in -- communtative/monoidal theories. This module refines the described -- algorithms for the special case of Abelian groups.
-- In this module, an Abelian group is a free algebra over a signature -- with three function symbols, -- -- * the binary symbol +, the group operator, -- * a constant 0, the identity element, and -- * the unary symbol -, the inverse operator. -- -- The algebra is generated by a set of variables. Syntactically, a -- variable is an identifer such as x and y.
-- The axioms associated with the algebra are: -- -- * x + y = y + x Commutativity -- * (x + y) + z = x + (y + z) Associativity -- * x + 0 = x Group identity -- * x + -x = 0 Cancellation
-- A substitution maps variables to terms. A substitution s is -- extended to a term as follows. -- -- s(0) = 0 -- s(-t) = -s(t) -- s(t + t') = s(t) + s(t')
-- The unification problem is given the problem statement t =? t', -- find a substitution s such that s(t) = s(t') modulo the axioms of -- the algebra. The matching problem is to find substitution s such -- that s(t) = t' modulo the axioms.
-- A term is represented as the sum of factors, and a factor is the -- product of an integer coeficient and a variable or the group -- identity, zero. In this representation, every coeficient is -- non-zero, and no variable occurs twice.
-- A term can be represented by a finite map from variables to -- non-negative integers. To make the code easier to understand, -- association lists are used instead of Data.Map.
newtype Lin = Lin [(String, Int)]
-- Constructors
-- Identity element (zero) ide :: Lin ide = Lin []
-- Factors var :: Int -> String -> Lin var 0 _ = Lin [] var c x = Lin [(x, c)]
-- Invert by negating coefficients. neg :: Lin -> Lin neg (Lin t) = Lin $ map (\(x, c) -> (x, negate c)) t
-- Join terms ensuring that coefficients are non-zero, and no variable -- occurs twice. add :: Lin -> Lin -> Lin add (Lin t) (Lin t') = Lin $ foldr f t' t where f (x, c) t = case lookup x t of Just c' | c + c' == 0 -> remove x t | otherwise -> (x, c + c') : remove x t Nothing -> (x, c) : t
-- Remove the first pair in an association list that matches the key. remove :: Eq a => a -> [(a, b)] -> [(a, b)] remove _ [] = [] remove x (y@(z, _) : ys) | x == z = ys | otherwise = y : remove x ys
canonicalize :: Lin -> Lin canonicalize (Lin t) = Lin (sort t)
-- Convert a linearized term into an association list. assocs :: Lin -> [(String, Int)] assocs (Lin t) = t
term :: [(String, Int)] -> Lin term assoc = foldr f ide assoc where f (x, c) t = add t $ var c x
-- Unification and Matching
newtype Equation = Equation (Lin, Lin)
newtype Maplet = Maplet (String, Lin)
-- Unification is the same as matching when there are no constants unify :: Monad m => Equation -> m [Maplet] unify (Equation (t0, t1)) = match $ Equation (add t0 (neg t1), ide)
-- Matching in Abelian groups is performed by finding integer -- solutions to linear equations, and then using the solutions to -- construct a most general unifier. match :: Monad m => Equation -> m [Maplet] match (Equation (t0, t1)) = case (assocs t0, assocs t1) of ([], []) -> return [] ([], _) -> fail "no solution" (t0, t1) -> do subst <- intLinEq (map snd t0) (map snd t1) return $ mgu (map fst t0) (map fst t1) subst
-- Construct a most general unifier from a solution to a linear -- equation. The function adds the variables back into terms, and -- generates fresh variables as needed. mgu :: [String] -> [String] -> Subst -> [Maplet] mgu vars syms subst = foldr f [] (zip vars [0..]) where f (x, n) maplets = case lookup n subst of Just (factors, consts) -> Maplet (x, g factors consts) : maplets Nothing -> Maplet (x, var 1 $ genSym n) : maplets g factors consts = term (zip genSyms factors ++ zip syms consts) genSyms = map genSym [0..]
-- Generated variables start with this character. genChar :: Char genChar = 'g'
genSym :: Int -> String genSym i = genChar : show i
-- So why solve linear equations? Consider the matching problem -- -- c[0]*x[0] + c[1]*x[1] + ... + c[n-1]*x[n-1] =? -- d[0]*a[0] + d[1]*a[1] + ... + d[m-1]*a[m-1] -- -- with n variables and m constants. We seek a most general unifier s -- such that -- -- s(c[0]*x[0] + c[1]*x[1] + ... + c[n-1]*x[n-1]) = -- d[0]*a[0] + d[1]*a[1] + ... + d[m-1]*a[m-1] -- -- which is the same as -- -- c[0]*s(x[0]) + c[1]*s(x[1]) + ... + c[n-1]*s(x[n-1]) = -- d[0]*a[0] + d[1]*a[1] + ... + d[m-1]*a[m-1] -- -- Notice that the number of occurrences of constant a[0] in s(x[0]) -- plus s(x[1]) ... s(x[n-1]) must equal d[0]. Thus the mappings of -- the unifier that involve constant a[0] respect integer solutions of -- the following linear equation. -- -- c[0]*x[0] + c[1]*x[1] + ... + c[n-1]*x[n-1] = d[0] -- -- To compute a most general unifier, a most general integer solution -- to a linear equation must be found.
-- Integer Solutions of Linear Inhomogeneous Equations
type LinEq = ([Int], [Int])
-- A linear equation with integer coefficients is represented as a -- pair of lists of integers, the coefficients and the constants. If -- there are no constants, the linear equation represented by (c, []) -- is the homogeneous equation: -- -- c[0]*x[0] + c[1]*x[1] + ... + c[n-1]*x[n-1] = 0 -- -- where n is the length of c. Otherwise, (c, d) represents a -- sequence of inhomogeneous linear equations with the same -- left-hand-side: -- -- c[0]*x[0] + c[1]*x[1] + ... + c[n-1]*x[n-1] = d[0] -- c[0]*x[0] + c[1]*x[1] + ... + c[n-1]*x[n-1] = d[1] -- ... -- c[0]*x[0] + c[1]*x[1] + ... + c[n-1]*x[n-1] = d[m-1] -- -- where m is the length of d.
type Subst = [(Int, LinEq)]
-- A solution is a partial map from variables to terms, and a term is -- a pair of lists of integers, the variable part of the term followed -- by the constant part. The variable part may specify variables not -- in the input. For example, the solution of -- -- 64x = 41y + 1 -- -- is x = -41z - 16 and y = -64z - 25. The computed solution is read -- off the list returned as an answer. -- -- intLinEq [64,-41] [1] = -- [(0,([0,0,0,0,0,0,-41],[-16])), -- (1,([0,0,0,0,0,0,-64],[-25]))]
-- Find integer solutions to linear equations intLinEq :: Monad m => [Int] -> [Int] -> m Subst intLinEq coefficients constants = intLinEqLoop (length coefficients) (coefficients, constants) []
-- The algorithm used to find solutions is described in Vol. 2 of The -- Art of Computer Programming / Seminumerical Alorithms, 2nd Ed., -- 1981, by Donald E. Knuth, pg. 327.
-- On input, n is the number of variables in the original problem, c -- is the coefficients, d is the constants, and subst is a list of -- eliminated variables. intLinEqLoop :: Monad m => Int -> LinEq -> Subst -> m Subst intLinEqLoop n (c, d) subst = -- Find the smallest coefficient in absolute value let (i, ci) = smallest c in case () of _ | ci < 0 -> intLinEqLoop n (invert c, invert d) subst -- Ensure the smallest coefficient is positive | ci == 0 -> fail "bad problem" -- Lack of non-zero coefficients is an error | ci == 1 -> -- A general solution of the following form has been found: -- x[i] = sum[j] -c'[j]*x[j] + d[k] for all k -- where c' is c with c'[i] = 0. return $ eliminate n (i, (invert (zero i c), d)) subst | divisible ci c -> -- If all the coefficients are divisible by c[i], a solution is -- immediate if all the constants are divisible by c[i], -- otherwise there is no solution. if divisible ci d then let c' = divide ci c d' = divide ci d in return $ eliminate n (i, (invert (zero i c'), d')) subst else fail "no solution" | otherwise -> -- Eliminate x[i] in favor of freshly created variable x[n], -- where n is the length of c. -- x[n] = sum[j] (c[j] div c[i] * x[j]) -- The new equation to be solved is: -- c[i]*x[n] + sum[j] c'[j]*x[j] = d[k] for all k -- where c'[j] = c[j] mod c[i] for j /= i and c'[i] = 0. let c' = map (\x -> mod x ci) (zero i c) c'' = divide ci (zero i c) subst' = eliminate n (i, (invert c'' ++ [1], [])) subst in intLinEqLoop n (c' ++ [ci], d) subst'
-- Find the smallest coefficient in absolute value smallest :: [Int] -> (Int, Int) smallest xs = foldl f (-1, 0) (zip [0..] xs) where f (i, n) (j, x) | n == 0 = (j, x) | x == 0 || abs n <= abs x = (i, n) | otherwise = (j, x)
invert :: [Int] -> [Int] invert t = map negate t
-- Zero the ith position in a list zero :: Int -> [Int] -> [Int] zero _ [] = [] zero 0 (_:xs) = 0 : xs zero i (x:xs) = x : zero (i - 1) xs
-- Eliminate a variable from the existing substitution. If the -- variable is in the original problem, add it to the substitution. eliminate :: Int -> (Int, LinEq) -> Subst -> Subst eliminate n m@(i, (c, d)) subst = if i < n then m : map f subst else map f subst where f m'@(i', (c', d')) = -- Eliminate i in c' if it occurs in c' case get i c' of 0 -> m' -- i is not in c' ci -> (i', (addmul ci (zero i c') c, addmul ci d' d)) -- Find ith coefficient get _ [] = 0 get 0 (x:_) = x get i (_:xs) = get (i - 1) xs -- addnum n xs ys sums xs and ys after multiplying ys by n addmul 1 [] ys = ys addmul n [] ys = map (* n) ys addmul _ xs [] = xs addmul n (x:xs) (y:ys) = (x + n * y) : addmul n xs ys
divisible :: Int -> [Int] -> Bool divisible small t = all (\x -> mod x small == 0) t
divide :: Int -> [Int] -> [Int] divide small t = map (\x -> div x small) t
-- Input and Output
instance Show Lin where showsPrec _ (Lin []) = showString "0" showsPrec _ x = showFactor t . showl ts where Lin (t:ts) = canonicalize x showFactor (x, 1) = showString x showFactor (x, -1) = showChar '-' . showString x showFactor (x, c) = shows c . showString x showl [] = id showl ((s,n):ts) | n < 0 = showString " - " . showFactor (s, negate n) . showl ts showl (t:ts) = showString " + " . showFactor t . showl ts
instance Read Lin where readsPrec _ s0 = [ (t1, s2) | (t0, s1) <- readFactor s0, (t1, s2) <- readRest t0 s1 ] where readPrimary s0 = [ (t0, s1) | (x, s1) <- scan s0, isVar x, let t0 = var 1 x ] ++ [ (t0, s1) | ("0", s1) <- scan s0, (s, _) <- scan s1, not (isVar s), let t0 = ide ] ++ [ (t0, s2) | (n, s1) <- scan s0, isNum n, (x, s2) <- scan s1, isVar x, let t0 = var (read n) x ] ++ [ (t0, s3) | ("(", s1) <- scan s0, (t0, s2) <- reads s1, (")", s3) <- scan s2 ] readFactor s0 = [ (t1, s2) | ("-", s1) <- scan s0, (t0, s2) <- readPrimary s1, let t1 = neg t0 ] ++ [ (t0, s1) | (s, _) <- scan s0, s /= "-", (t0, s1) <- readPrimary s0 ] readRest t0 s0 = [ (t2, s3) | ("+", s1) <- scan s0, (t1, s2) <- readFactor s1, (t2, s3) <- readRest (add t0 t1) s2 ] ++ [ (t2, s3) | ("-", s1) <- scan s0, (t1, s2) <- readPrimary s1, (t2, s3) <- readRest (add t0 (neg t1)) s2 ] ++ [ (t0, s0) | (s, _) <- scan s0, s /= "+" && s /= "-" ]
isNum :: String -> Bool isNum (c:_) = isDigit c isNum _ = False
isVar :: String -> Bool isVar (c:_) = isAlpha c && c /= genChar isVar _ = False
scan :: ReadS String scan "" = [("", "")] scan (c:s) | isSpace c = scan s | isAlpha c = [ (c:part, t) | (part,t) <- [span isAlphaNum s] ] | isDigit c = [ (c:part, t) | (part,t) <- [span isDigit s] ] | otherwise = [([c], s)]
instance Show Equation where showsPrec _ (Equation (t0, t1)) = shows t0 . showString " = " . shows t1
instance Read Equation where readsPrec _ s0 = [ (Equation (t0, t1), s3) | (t0, s1) <- reads s0, ("=", s2) <- scan s1, (t1, s3) <- reads s2 ]
instance Show Maplet where showsPrec _ (Maplet (x, t)) = showString x . showString " -> " . shows t
-- Test Routine
-- Given an equation, display a unifier and a matcher. test :: String -> IO () test prob = case readM prob of Err err -> putStrLn err Ans (Equation (t0, t1)) -> do putStr "Problem: " print $ Equation (canonicalize t0, canonicalize t1) subst <- unify $ Equation (t0, t1) putStr "Unifier: " print subst putStr "Matcher: " case match $ Equation (t0, t1) of Err err -> putStrLn err Ans subst -> print subst putStrLn ""
readM :: (Read a, Monad m) => String -> m a readM s = case [ x | (x, t) <- reads s, ("", "") <- lex t ] of [x] -> return x [] -> fail "no parse" _ -> fail "ambiguous parse"
data AnsErr a = Ans a | Err String
instance Monad AnsErr where (Ans x) >>= k = k x (Err s) >>= _ = Err s return = Ans fail = Err
main :: IO () main = do done <- isEOF case done of True -> return () False -> do prob <- getLine test prob main

Hi, I ran your code thought HLint (http://community.haskell.org/~ndm/hlint), and it suggested a couple of things (mainly eta reduce). The most interesting suggestions are on your main function:
main :: IO () main = do done <- isEOF case done of True -> return () False -> do prob <- getLine test prob main
It suggests: Example.lhs:432:3: Warning: Use if Found: case done of True -> return () False -> do prob <- getLine test prob main Why not: if done then return () else do prob <- getLine test prob main Changing that and rerunning says: Example.lhs:432:3: Error: Use unless Found: if done then return () else do prob <- getLine test prob main Why not: unless done $ do prob <- getLine test prob main So I (or rather HLint) recommends you do:
main :: IO () main = do done <- isEOF unless done $ do prob <- getLine test prob main
Thanks, Neil

Hello Neil, Wednesday, August 19, 2009, 2:16:06 PM, you wrote:
main = do done <- isEOF unless done $ do prob <- getLine test prob main
main = untilM isEOF (getLine >>= test) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Wed, Aug 19, 2009 at 6:16 AM, Neil Mitchell
Why not: if done then return () else do prob <- getLine test prob main
I've given up on using if-then-else in do expressions. They confuse emacs. There is a proposal for Haskell' to fix the problem, but until then, I will not use them in do expressions. I'm so glad new languages do not use the offset rule. I get tired typing tab in emacs, especially since for most other languages, emacs does so well at picking a good indent. Requiring coders to spend so much time choosing indents reminds me of the days when I wrote C code with vi. I've been there, done that, and moved on to emacs.
unless done $ do prob <- getLine test prob main
I do like this suggestion. Thanks. John

Hi
I've given up on using if-then-else in do expressions. They confuse emacs. There is a proposal for Haskell' to fix the problem, but until then, I will not use them in do expressions.
It's a shame, there are ways of indenting them that work, but they're not as natural. It's a wart, but it will be fixed.
I'm so glad new languages do not use the offset rule.
F# is new and has the offset rule. Haskell is old and has the optional offset rule: do { prob <- getLine ; test prob ; main} Now your indentation is your own :-) Some people prefer this style. Simon Peyton Jones uses it in the book beautiful code. I much prefer indentation only. Thanks Neil

On Wed, Aug 19, 2009 at 6:51 AM, Neil Mitchell
F# is new and has the offset rule. Haskell is old and has the optional offset rule:
I thought F# uses OCaml syntax. Emacs does well with OCaml syntax. Guy Steele told this story at a conference. As part of the Fortress design effort, he and other at Sun visited several sites that make use of high performance computing. They received a variety of suggestions on how to design a high productivity language for high performance computing, and uniformly were asked not to give programmers a language that uses the offset rule. John

... Haskell is old and has the optional offset rule:
do { prob <- getLine ; test prob ; main}
It's interesting to see people put semicolons at the begining of a line of code. In 1970s, people used to draw lines on printouts of Ada and Pascal code to connect the begins with the ends. My first publication Ramsdell, J. D., "Prettyprinting Structured Programs with Connector Lines," ACM SIGPLAN Notices, Vol. 14, No. 9, p. 74, September 1979 suggested prettyprinting Ada and Pascal programs with the semicolons at the begining of the lines and use them as the connector lines. Thus a prettyprinted Ada program looked like: package Mine is ... begin ; while i < Integer'Last loop ; ; Print (i) ; end loop; end Mine; It didn't work quite as well in Pascal, because semicolon was a statement separator instead of a statement terminator. In those day, procedures tended to large and deeply nested because procedure invocation was expensive. John

Hello John, Tuesday, August 25, 2009, 4:51:16 AM, you wrote:
In those day, procedures tended to large and deeply nested because procedure invocation was expensive.
interesting story. in 80s, virtual method call was expensive. now lazy evaluation is expensive. what's next? :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

John D. Ramsdell wrote:
On Wed, Aug 19, 2009 at 6:16 AM, Neil Mitchell
wrote: Why not: if done then return () else do prob <- getLine test prob main
I've given up on using if-then-else in do expressions. They confuse emacs. There is a proposal for Haskell' to fix the problem, but until then, I will not use them in do expressions.
Do not blame haskell, blame emacs, if emacs is so stupid. Fortunately there is a better emacs mode which understands layout and if: http://kuribas.hcoop.net/haskell-indentation.el
I'm so glad new languages do not use the offset rule. I get tired typing tab in emacs, especially since for most other languages, emacs does so well at picking a good indent. Requiring coders to spend so much time choosing indents reminds me of the days when I wrote C code with vi. I've been there, done that, and moved on to emacs.
Do not blame haskell, blame emacs. The layout rule is simple to understand and I think it makes attractive code. It's not haskell's fault that the emacs mode chooses a bad indent so often. There is a better emacs mode which gets the indentation right more often, I find ;) http://kuribas.hcoop.net/haskell-indentation.el Jules

John D. Ramsdell wrote:
On Wed, Aug 19, 2009 at 8:32 AM, Jules Bean
wrote: Do not blame haskell, blame emacs, if emacs is so stupid.
How can you blame emacs? Do you expect emacs to read programmer's minds?
No, I expect emacs to select a suitable first indentation guess and give the programmer a natural way to choose alternative ones. I don't think the initial haskell-mode implementation had that property. I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant.

On Thu, Aug 20, 2009 at 9:08 AM, Jules Bean
I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant.
Let's put this issue in perspective. For those few Haskell programmers that do find layout irritating, I'm sure we would all agree it's but a minor irritation. The real downside of layout is if non-Haskell programmers use it as an excuse to dismiss the language. I happen to think that Data Parallel Haskell has great potential for use in high performance computations. I'd hate to see a bunch of Fortraners not try DPH because of Haskell syntax. In terms of irritating programmers, I think Wirth takes the cake. After advancing the art with Pascal, he correctly saw its lack of modules as a problem, and he solved the issue with the Modular-2 programming language. He made the improvement, but also required programmers to type keywords in all caps! I tried Modular-2 and quickly tired of using the caps lock key. Maude has this problem too. Very irritating. John

John D. Ramsdell wrote:
On Thu, Aug 20, 2009 at 9:08 AM, Jules Bean
wrote: I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant.
Let's put this issue in perspective. For those few Haskell programmers that do find layout irritating, I'm sure we would all agree it's but a minor irritation. The real downside of layout is if non-Haskell programmers use it as an excuse to dismiss the language. I happen to think that Data Parallel Haskell has great potential for use in high performance computations. I'd hate to see a bunch of Fortraners not try DPH because of Haskell syntax.
Well that's a reasonable point. They can still use the non-layout form if it bothers them that much?

Let me put all my cards on the table. You see, I really am only
slightly irrigated by offset syntax. In contrast, I am a strong
proponent of functional programming for parallel programming. In my
opinion, it has to be the "new way" for multiprocessor machines. Just
think about it and if other paradym could possibly work. We've tried
many on them. Many years ago, I wrote SISAl programs. There were
many good ideas in SISAL, but it did not catch on. Perhaps Data
Parallel Haskell will catch on. In my opinion, something like it is
the ``answer.'' Even though the code I submitted is not parallel,
I've thought about how to make it so. And isn't thinking parallelism
iour future? I think so.
John
On Thu, Aug 20, 2009 at 10:04 AM, Jules Bean
John D. Ramsdell wrote:
On Thu, Aug 20, 2009 at 9:08 AM, Jules Bean
wrote: I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant.
Let's put this issue in perspective. For those few Haskell programmers that do find layout irritating, I'm sure we would all agree it's but a minor irritation. The real downside of layout is if non-Haskell programmers use it as an excuse to dismiss the language. I happen to think that Data Parallel Haskell has great potential for use in high performance computations. I'd hate to see a bunch of Fortraners not try DPH because of Haskell syntax.
Well that's a reasonable point.
They can still use the non-layout form if it bothers them that much?

Even if you are only slightly irritated by offset syntax, why are you using it?
{;} works fine.
On Sat, Aug 22, 2009 at 3:51 AM, John D. Ramsdell
Let me put all my cards on the table. You see, I really am only slightly irrigated by offset syntax. In contrast, I am a strong proponent of functional programming for parallel programming. In my opinion, it has to be the "new way" for multiprocessor machines. Just think about it and if other paradym could possibly work. We've tried many on them. Many years ago, I wrote SISAl programs. There were many good ideas in SISAL, but it did not catch on. Perhaps Data Parallel Haskell will catch on. In my opinion, something like it is the ``answer.'' Even though the code I submitted is not parallel, I've thought about how to make it so. And isn't thinking parallelism iour future? I think so.
John
On Thu, Aug 20, 2009 at 10:04 AM, Jules Bean
wrote: John D. Ramsdell wrote:
On Thu, Aug 20, 2009 at 9:08 AM, Jules Bean
wrote: I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant.
Let's put this issue in perspective. For those few Haskell programmers that do find layout irritating, I'm sure we would all agree it's but a minor irritation. The real downside of layout is if non-Haskell programmers use it as an excuse to dismiss the language. I happen to think that Data Parallel Haskell has great potential for use in high performance computations. I'd hate to see a bunch of Fortraners not try DPH because of Haskell syntax.
Well that's a reasonable point.
They can still use the non-layout form if it bothers them that much?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Aug 20, 2009 at 9:08 AM, Jules Bean
I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant.
Let's put this issue in perspective. For those few Haskell programmers that do find layout irritating, I'm sure we would all agree it's but a minor irritation. The real downside of layout is if non-Haskell programmers use it as an excuse to dismiss the language. I happen to think that Data Parallel Haskell has great potential for use in high performance computations. I'd hate to see a bunch of Fortraners not try DPH because of Haskell syntax. In terms of irritating programmers, I think Wirth takes the cake. After advancing the art with Pascal, he correctly saw its lack of modules as a problem, and he solved the issue with the Modular-2 programming language. He made the improvement, but also required programmers to type keywords in all caps! I tried Modular-2 and quickly tired of using the caps lock key. Maude has this problem too. Very irritating. John

John D. Ramsdell
I've been studying equational unification. I decided to test my understanding of it by implementing unification and matching in Abelian groups. I am quite surprised by how little code it takes. Let me share it with you.
Thanks! Another small change that might shorten the code is to use Data.Map for linear combinations: type Lin = Data.Map.Map String Int -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig Shaik Riaz

On Wed, Aug 19, 2009 at 11:38 PM, Chung-chieh
Shan
Thanks! Another small change that might shorten the code is to use Data.Map for linear combinations:
I chose to use association lists because I did not want to explain the adjust function one would use to implement the add function. I thought it would make the code cryptic for beginners. Your suggestion does raise an interesting question. When is it faster to to use associations list instead of Data.Map. For some applications of the matcher, the number of variables is usually, but not always small, like less than three, so association lists may actually be faster. I never know the number of keys it takes to make the overhead of Data.Map worthwhile. I also never know the number elements it takes to make the overhead of an array worthwhile over a list in applications that do a lot of indexing. John

The patch avoids a redundant zeroing of c[i]. $ diff -u {a,b}/Main.lhs --- a/Main.lhs 2009-08-23 21:07:08.000000000 -0400 +++ b/Main.lhs 2009-08-23 21:09:54.000000000 -0400 @@ -255,12 +255,11 @@
-- where n is the length of c. -- x[n] = sum[j] (c[j] div c[i] * x[j]) -- The new equation to be solved is:
-> -- c[i]*x[n] + sum[j] c'[j]*x[j] = d[k] for all k -> -- where c'[j] = c[j] mod c[i] for j /= i and c'[i] = 0. -> let c' = map (\x -> mod x ci) (zero i c) -> c'' = divide ci (zero i c) -> subst' = eliminate n (i, (invert c'' ++ [1], [])) subst in -> intLinEqLoop n (c' ++ [ci], d) subst' +> -- c[i]*x[n] + sum[j] (c[j] mod c[i])*x[j] = d[k] for all k +> intLinEqLoop n (map (\x -> mod x ci) c ++ [ci], d) subst' +> where +> subst' = eliminate n (i, (invert c' ++ [1], [])) subst +> c' = divide ci (zero i c)
-- Find the smallest coefficient in absolute value smallest :: [Int] -> (Int, Int)
$

I cleaned up the code, partitioned it into a library and an executable, and made the package available on hackage as agum-1.0. Enjoy. John
participants (6)
-
Bulat Ziganshin
-
Chung-chieh Shan
-
John D. Ramsdell
-
Jules Bean
-
Lennart Augustsson
-
Neil Mitchell