On 08-Apr-2001, Terrence Brannon <[EMAIL PROTECTED]> 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
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 <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
                                    |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.

_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to