Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-24 Thread John D. Ramsdell
 ... 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-24 Thread Bulat Ziganshin
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,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-23 Thread John D. Ramsdell
On Sat, Aug 22, 2009 at 8:30 PM, Lennart
Augustssonlenn...@augustsson.net wrote:
 Even if you are only slightly irritated by offset syntax, why are you using 
 it?
 {;} works fine.

I hadn't thought about that option.  I'll give it a try on my next program.

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


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-22 Thread Lennart Augustsson
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. Ramsdellramsde...@gmail.com wrote:
 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 Beanju...@jellybean.co.uk wrote:
 John D. Ramsdell wrote:

 On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk 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

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


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-21 Thread 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 Beanju...@jellybean.co.uk wrote:
 John D. Ramsdell wrote:

 On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk 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


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread John D. Ramsdell
On Wed, Aug 19, 2009 at 8:32 AM, Jules Beanju...@jellybean.co.uk 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?

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


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread Jules Bean

John D. Ramsdell wrote:

On Wed, Aug 19, 2009 at 8:32 AM, Jules Beanju...@jellybean.co.uk 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.

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


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread John D. Ramsdell
On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk 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.

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread John D. Ramsdell
On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk 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.

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread Jules Bean

John D. Ramsdell wrote:

On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk 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


[Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-19 Thread 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.

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 = 0Cancellation

 -- 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 

Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-19 Thread Neil Mitchell
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-19 Thread Bulat Ziganshin
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,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-19 Thread John D. Ramsdell
On Wed, Aug 19, 2009 at 6:16 AM, Neil Mitchellndmitch...@gmail.com 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.

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-19 Thread Neil Mitchell
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-19 Thread John D. Ramsdell
On Wed, Aug 19, 2009 at 6:51 AM, Neil Mitchellndmitch...@gmail.com wrote:

 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-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-19 Thread Jules Bean

John D. Ramsdell wrote:

On Wed, Aug 19, 2009 at 6:16 AM, Neil Mitchellndmitch...@gmail.com 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe