What do you think about Mercury?

I have decided to escape the world of Perl into something more definitional. I gave up on CAML and Erlang because they contain imperative elements and I am tired of that form of coding. So, I have narrowed it down to Haskell and Mercury. The attractive things about Haskell are: - automatic generation of concurrent programs from normal source... instead of sending msgs to processes like in Erlang. - large user base - possible real job in industry (with Galois Connections). - several books based on it - binaries available (even for my mac os x box already!). So, with that said, http://www.cs.mu.oz.au/research/mercury/information/comparison_with_haskell.... lists a number of advantages of Mercury over Haskell. And both Haskell and Mercury did well in the ICFP. Does anyone have anything to say about these criticisms? There were two particular things in the list that caught my attention: 1- Haskell is a pure functional language, but I don't see any support for backtracking or other logic features... but my guess is you have some way of handling this? How? 2- Mercury's mode system provides support for subtypes. For example, you can declare that a function whose argument is a discriminated union type accepts only a subset of the possible constructors for that type, and the mode system will enforce this.

On 08-Apr-2001, Terrence Brannon
1- Haskell is a pure functional language, but I don't see any support for backtracking or other logic features... but my guess is you have some way of handling this? How?
The usual way of handling backtracking in Haskell is using lazy lists.
See Phil Wadler's 1985 paper [1].
For an example of this, I've attached a program for solving the
8-queens problem; you can compare this one with the Mercury version
in tests/benchmarks/queens.m in the mercury-tests distribution.
(Probably neither this one nor the Mercury one are ideal style,
but I happened to have them lying around...)
So backtracking is really not that hard to emulate in a lazy functional
language. Supporting logic variables and constraint solving is a lot
more cumbersome, however.
References
[1] Philip Wadler: How to Replace Failure by a List of Successes: A
method for exception handling, backtracking, and pattern matching in
lazy functional languages. FPCA 1985: 113-128
-- main = print_all_solns 8
main = print_soln_count 9
print_soln_count :: Int -> IO ()
print_soln_count n = putStrLn (show (length (solutions n)))
print_all_solns :: Int -> IO ()
print_all_solns n = sequence (map show_soln (solutions n))
solutions :: Int -> [[Int]]
solutions n = queens (start n)
show_soln :: Show a => a -> IO ()
show_soln soln = putStrLn (show soln)
start :: Int -> [Int]
start n = [1 .. n]
queens :: [Int] -> [[Int]]
queens start_posn = [ posn | posn <- qperm start_posn, safe posn ]
qperm :: [t] -> [[t]]
qperm [] = [[]]
qperm (x:xs) = [(y:zs) | zs <- qperm ys, (y,ys) <- qdelete (x:xs) ]
qdelete :: [t] -> [(t,[t])]
qdelete [] = []
qdelete (x:xs) = ((x,xs) : [ (y,(x:ys)) | (y,ys) <- qdelete xs ])
safe :: [Int] -> Bool
safe [] = True
safe (n:l) = nodiag n 1 l && safe l
nodiag :: Int -> Int -> [Int] -> Bool
nodiag _ _ [] = True
nodiag b d (n:l) = d /= n - b && d /= b - n && nodiag b (d+1) l
--
Fergus Henderson

Fergus Henderson wrote:
On 08-Apr-2001, Terrence Brannon wrote:
1- Haskell is a pure functional language, but I don't see any support for backtracking or other logic features... but my guess is you have some way of handling this? How?
The usual way of handling backtracking in Haskell is using lazy lists. See Phil Wadler's 1985 paper [1].
For an example of this, I've attached a program for solving the 8-queens problem; you can compare this one with the Mercury version ...
This is a way to deal with *data backtracking*. Sure, most of classical combinatoric algorithms belong to this category, the gene- ration of permutations/combinations, 8 queens, etc. And of course the non-deterministic parsing. But there is also the question of *control backtracking*, used to emulate iterations, etc. This may be implemented functionally as well by using continuations. You may have conditional continuations, multiple continuations,... Unfortunately such techniques are rarely taught. I suspect that Mark Jones' Prolog implementation in Haskell/Gofer used them, but I don't remember the details. Jerzy Karczmarczuk Caen, France

On 09-Apr-2001, Jerzy Karczmarczuk
The usual way of handling backtracking in Haskell is using lazy lists. ... This is a way to deal with *data backtracking*. Sure, most of classical combinatoric algorithms belong to this category, the gene- ration of permutations/combinations, 8 queens, etc. And of course
Fergus Henderson wrote: the non-deterministic parsing.
But there is also the question of *control backtracking*, used to emulate iterations, etc. This may be implemented functionally as well by using continuations.
Using continuations to implement backtracking is another important idiom, I agree. (In fact, that is how the new back-end for the Mercury compiler deals with backtracking Mercury code: it converts it into C (or IL, or Java) code that uses continuation passing to handle the backtracing.) However, in a lazy functional language, I'm not sure that you can so easily or usefully distinguish between _control_ backtracking and _data_ backtracking. In a lazy functional language the control flow is mainly implicit rather than explicit, and is determined by the data flow.
You may have conditional continuations, multiple continuations,...
If you use other lazy data structures, e.g. lazy trees rather than lazy
lists, then you can do the same kinds of things that you could do using
conditional or multiple continuations.
--
Fergus Henderson

Mon, 9 Apr 2001 14:30:01 +1000, Fergus Henderson
For an example of this, I've attached a program for solving the 8-queens problem;
Here is mine, also using the list monad together with the state monad (uses StateT [] and not ListT State, so the state is restored during backtracking and not permanent). import Monad;import MonadState;main=mapM_(\s->mapM_ putStrLn$[]:[take 8$replicate i '.'++'Q':repeat '.'|i<-s])$evalStateT(mapM(\i->msum[do (/)<-get;guard$i/j;put(\x y->y/=j&&x+y/=i+j&&x-y/=i-j&&x/y);return j |j<-a])a)(\_ _->True);a=[0..7] -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

Several people, including myself in my long forgotten thesis, have shown
that these are equivalent.
Erik
----- Original Message -----
From: "Jerzy Karczmarczuk"
Fergus Henderson wrote:
On 08-Apr-2001, Terrence Brannon wrote:
1- Haskell is a pure functional language, but I don't see any support for backtracking or other logic features... but my guess is you have some way of handling this? How?
The usual way of handling backtracking in Haskell is using lazy lists. See Phil Wadler's 1985 paper [1].
For an example of this, I've attached a program for solving the 8-queens problem; you can compare this one with the Mercury version ...
This is a way to deal with *data backtracking*. Sure, most of classical combinatoric algorithms belong to this category, the gene- ration of permutations/combinations, 8 queens, etc. And of course the non-deterministic parsing.
But there is also the question of *control backtracking*, used to emulate iterations, etc. This may be implemented functionally as well by using continuations. You may have conditional continuations, multiple continuations,... Unfortunately such techniques are rarely taught.
I suspect that Mark Jones' Prolog implementation in Haskell/Gofer used them, but I don't remember the details.
Jerzy Karczmarczuk Caen, France
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) wrote,
Mon, 9 Apr 2001 14:30:01 +1000, Fergus Henderson
pisze: For an example of this, I've attached a program for solving the 8-queens problem;
Here is mine, also using the list monad together with the state monad (uses StateT [] and not ListT State, so the state is restored during backtracking and not permanent).
import Monad;import MonadState;main=mapM_(\s->mapM_ putStrLn$[]:[take 8$replicate i '.'++'Q':repeat '.'|i<-s])$evalStateT(mapM(\i->msum[do (/)<-get;guard$i/j;put(\x y->y/=j&&x+y/=i+j&&x-y/=i-j&&x/y);return j |j<-a])a)(\_ _->True);a=[0..7]
I always knew that inside Haskell there is a Perl trying to get out! Manuel

On Tue, Apr 10, 2001 at 11:16:27AM +1000, Manuel M. T. Chakravarty wrote:
I always knew that inside Haskell there is a Perl trying to get out!
import List;q _ _ 0 _=[[]];q u i r k=let{b=[x+1|x<-u,-1>x||x>0,x

On 08-Apr-2001, Terrence Brannon
I have decided to escape the world of Perl into something more definitional. I gave up on CAML and Erlang because they contain imperative elements and I am tired of that form of coding. So, I have narrowed it down to Haskell and Mercury.
...
http://www.cs.mu.oz.au/research/mercury/information/comparison_with_haskell....
That page really only describes the differences in the type systems.
A very important distinction between Mercury and Haskell which that page
just skims over is that Haskell is lazy by default, and Mercury is not.
--
Fergus Henderson
participants (7)
-
elf@sandburst.com
-
Erik Meijer
-
Fergus Henderson
-
Jerzy Karczmarczuk
-
Manuel M. T. Chakravarty
-
qrczak@knm.org.pl
-
Terrence Brannon