RE: Non-determinism, backtracking and Monads

Check out "Embedding Prolog in Haskell", which explores exactly the
topic you discuss.
http://citeseer.nj.nec.com/272378.html
Simon
| -----Original Message-----
| From: haskell-cafe-admin@haskell.org
[mailto:haskell-cafe-admin@haskell.org] On Behalf Of Graham
| Klyne
| Sent: 11 June 2003 08:38
| To: Jerzy Karczmarczuk; Haskell Cafe
| Subject: Non-determinism, backtracking and Monads
|
| At 11:06 05/06/03 +0200, Jerzy Karczmarczuk wrote:
| >I permit myself to observe that your powerset problem (and the
restricted
| >length problem, i.e. the combinations) is usually solved in Prolog,
through
| >backtracking, using reasoning/style which adopts this
"individualistic"
| >philosophy.
| >
| >powerset(<source>,<possible result>) --- is the pattern. And the
| >solution is
| >
| >powerset([],[]). Since nothing else can be done. Otherwise you pick
the item
| > or not.
| >
| >powerset([X|Rest],L) :- powerset(Rest,L).
| >powerset([X|Rest],[X|L) :- powerset(Rest,L).
| >
| >The xxx ++ map (x :) xxx solution in Haskell is a particular
formulation
| >(and optimization) of the straightforward transformation from a
version
| >using the non-deterministic Monad. This one is really almost a carbon
copy
| >of the Prolog solution, with appropriate "lifting" of operations from
| >individuals to lazy lists.
|
| I was thinking some more about this comment of yours, and my own
experience
| with the ease of using lists to implement prolog-style generators, and
| think I come to some better understanding. If I'm right, I assume the
| following is common knowledge to experienced Haskell programmers. So,
in
| the spirit of testing my understanding...
|
| The common thread here is a non-deterministic calculation in which
there
| are several possible solutions for some problem. The goal is to find
(a)
| if there are any solutions, and (b) one, more or all of the solutions.
|
| Prolog does this, absent ! (cut), by backtracking through the possible
| solutions.
|
| My first epiphany is that the Haskell idea of using a lazily evaluated
list
| for result of a non-deterministic computation is pretty much the same
thing
| (which is pretty much what you said? Is this what you mean by "the
| non-deterministic monad"?). The mechanisms for accessing a list mean
that
| the solutions must be accessed in the order they are generated, just
like
| Prolog backtracking.
|
| So there seems to be a very close relationship between the lazy list
and
| non-deterministic computations, but what about other data structures?
I
| speculate that other structures, lazily evaluated, may also be used to
| represent the results of non-deterministic computations, yet allow the
| results to be accessed in a different order. And these, too, may be
| (should be?) monads. If so, the Haskell approach might be viewed as a
| generalization of Prolog's essentially sequential backtracking.
|
| In a private message concerning the powerset thread on this list, a
| correspondent offered a program to evaluate the subsets in size order,
| which I found particularly elegant:
|
| >ranked_powerset :: [a] -> [[[a]]]
| >ranked_powerset = takeWhile (not . null) . foldr next_powerset ([[]]
:
| repeat [])
| >
| >next_powerset :: a -> [[[a]]] -> [[[a]]]
| >next_powerset x r = zipWith (++) ([] : map (map (x:)) r) r
| >
| >powerset :: [a] -> [[a]]
| >powerset = tail . concat . ranked_powerset
|
| They also pointed out that "ranked_powerset is handy since you can use
it
| to define combinatorial choice etc.":
|
| > choose :: Int -> [a] -> [[a]]
| > choose k = (!! k) . ranked_powerset
|
| So here is an example of a different structure (a list of lists) also
used
| to represent a non-deterministic computation, and furthermore
providing
| means to access the results in some order other than a single linear
| sequences (e.g. could be used to enumerate all the powersets
containing the
| nth member of the base set, *or* all the powersets of a given size,
without
| evaluating all of the other powersets).
|
| To test this idea, I think it should be possible to define a monad
based on
| a simple tree structure, which also can be used to represent the
results of
| a non-deterministic computation. An example of this is below, at the
end
| of this message, which seems to exhibit the expected properties.
|
| So if the idea of representing a non-deterministic computation can be
| generalized from a list to a tree, why not to other data structures?
My
| tree monad is defined wholly in terms of reduce and fmap. Without
going
| through the exercise, I think the reduce function might be definable
in
| terms of fmap for any data type of the form "Type (Maybe a)", hence
| applicable to a range of functors? In particular, I'm wondering if it
can
| be applied to any gmap-able structure over a Maybe type.
|
| I'm not sure if this is of any practical use; rather it's part of my
| attempts to understand the relationship between functors and monads
and
| other things functional.
|
| #g
| --
|
|
| [[
| -- spike-treemonad.hs
|
| data Tree a = L (Maybe a) | T { l,r :: Tree a }
| deriving Eq
|
| instance (Show a) => Show (Tree a) where
| show t = (showTree "" t) ++ "\n"
|
| showTree :: (Show a) => String -> Tree a -> String
| showTree _ (L Nothing ) = "()"
| showTree _ (L (Just a)) = show a
| showTree i (T l r) = "( " ++ (showTree i' l) ++ "\n" ++
| i' ++ (showTree i' r) ++ " )"
| where i' = ' ':' ':i
|
| instance Functor Tree where
| fmap f (L Nothing) = L Nothing
| fmap f (L (Just a)) = L (Just (f a))
| fmap f (T l r) = T (fmap f l) (fmap f r)
|
| reduce :: Tree (Tree a) -> Tree a
| reduce (L Nothing) = L Nothing
| reduce (L (Just (L Nothing ) )) = L Nothing
| reduce (L (Just (L (Just a)) )) = L (Just a)
| reduce (L (Just (T l r ) )) = T l r
| reduce (T l r) = T (reduce l) (reduce r)
|
| instance Monad Tree where
| -- L Nothing >>= k = L Nothing
| t >>= k = reduce $ fmap k t
| return x = L (Just x)
| fail s = L Nothing
|
| -- tests
|
| t1 :: Tree String
| t1 = T (L $ Just "1")
| (T (T (T (L $ Just "211")
| (L $ Just "311"))
| (L Nothing))
| (L $ Just "22"))
|
| k1 :: a -> Tree a
| k1 n = T (L $ Just n) (L $ Just n)
|
| r1 = t1 >>= k1
|
| k2 :: String -> Tree String
| k2 s@('1':_) = L $ Just s
| k2 s@('2':_) = T (L $ Just s) (L $ Just s)
| k2 _ = L Nothing
|
| r2 = t1 >>= k2
|
| t3 = L Nothing :: Tree String
| r3 = t3 >>= k1
|
| r4 = t1 >>= k1 >>= k2
| r5 = (return "11") :: Tree String
| r6 = r5 >>= k1
|
| -- Check out monad laws
| -- return a >>= k = k a
| m1a = (return t1) >>= k1
| m1b = k1 t1
| m1c = m1a == m1b
|
| -- m >>= return = m
| m2a = t1 >>= return
| m2b = t1
| m2c = m2a == m2b
|
| -- m >>= (\x -> k x >>= h) = (m >>= k) >>= h
| m3a = t1 >>= (\x -> k1 x >>= k2)
| m3b = (t1 >>= k1) >>= k2
| m3c = m3a == m3b
| ]]
|
|
| -------------------
| Graham Klyne
|

On Wed, 11 Jun 2003 09:03:32 +0100
"Simon Peyton-Jones"
Check out "Embedding Prolog in Haskell", which explores exactly the topic you discuss.
http://citeseer.nj.nec.com/272378.html
Simon
and what can be considered a followup to that paper, http://citeseer.nj.nec.com/claessen00typed.html -- solve (do (x,y) <- free; append x y (s2l "abc"); -- liftM2 (,) (list atom x) (list atom y)) ==> -- ([],["a","b","c"]),(["a"],["b","c"]),(["a","b"],["c"]),(["a","b","c"],[ ]) append :: (Unify s a, Free s a) => List s a -> List s a -> List s a -> LP s () append ps qs rs = (do ps =:= Nil qs =:= rs) `mplus` (do (x,xs,ys) <- free ps =:= (x ::: xs) rs =:= (x ::: ys) append xs qs ys) -- append([],L,L). -- append([H|T],L,[H|Rest]) :- append(T,L,Rest). powerset' xs ys = free >>= \(h,t,rest) -> p2h [ [xs =:= Nil, ys =:= Nil], [xs =:= (h ::: t), powerset' t ys], [xs =:= (h ::: t), ys =:= (h ::: rest), powerset' t rest]] -- powerset([],[]). -- powerset([X|Xs],Rest) :- powerset(Xs,Rest) -- powerset([X|Xs],[X|Rest]) :- powerset(Xs,Rest).
participants (2)
-
Derek Elkins
-
Simon Peyton-Jones