Implementation of Non-Deterministic State Machine

Hello, As an exercice to learn monadic programming, I programmed a Non-Deterministic State Machine. I extended the exercice to include the deterministic "cut" function, exactly as the one existing in Prolog. That means I defined an evalutaion frame, and if the machine evaluates a "cut", that means no other alternatives are to be evaluated in the inner-most frame. In Prolog, each predicates defines also a frame. To further extend my experiment, I wanted to implement my State Machine as a Monad Transformer. But there, even if it's working, I cannot anymore work with infinite choice points :( So I was looking for some existing implementation, to try understand what I did and even if it is possible. Thanks, Pierre -- Pierre Barbier de Reuille INRA - UMR Cirad/Inra/Cnrs/Univ.MontpellierII AMAP Botanique et Bio-informatique de l'Architecture des Plantes TA40/PSII, Boulevard de la Lironde 34398 MONTPELLIER CEDEX 5, France tel : (33) 4 67 61 65 77 fax : (33) 4 67 61 56 68

Hello, You could look at the implementation of backtracking tarnsformer (BackT) in my monad library: http://www.cse.ogi.edu/~diatchki/monadLib/ The version there is written in continuation passing style so it may be a tad confusing at first. Another (similar in principle) implementation is like this:
module BackT where
import Monad(MonadPlus(..))
newtype BackT m a = B { unB :: m (Answer m a) } data Answer m a = Fail | Done a | Choice (BackT m a) (BackT m a)
instance Monad m => Monad (BackT m) where return a = B (return (Done a)) B m >>= k = B (do x <- m case x of Fail -> return Fail Done a -> unB (k a) Choice m1 m2 -> return (Choice (m1 >>= k) (m2 >>= k)) )
lift :: Monad m => m a -> BackT m a lift m = B (do x <- m return (Done x))
instance Monad m => MonadPlus (BackT m) where mzero = B (return Fail) mplus m1 m2 = B (return (Choice m1 m2))
Then you can write different tarversal schemas that perform the
effects in different ways, e.g. find all answers in breadth first
manner, or find one answer in depth first manner, etc.
-Iavor
On Mon, 28 Mar 2005 17:58:48 +0200, Pierre Barbier de Reuille
Hello,
As an exercice to learn monadic programming, I programmed a Non-Deterministic State Machine. I extended the exercice to include the deterministic "cut" function, exactly as the one existing in Prolog. That means I defined an evalutaion frame, and if the machine evaluates a "cut", that means no other alternatives are to be evaluated in the inner-most frame. In Prolog, each predicates defines also a frame.
To further extend my experiment, I wanted to implement my State Machine as a Monad Transformer. But there, even if it's working, I cannot anymore work with infinite choice points :(
So I was looking for some existing implementation, to try understand what I did and even if it is possible.
Thanks,
Pierre
-- Pierre Barbier de Reuille
INRA - UMR Cirad/Inra/Cnrs/Univ.MontpellierII AMAP Botanique et Bio-informatique de l'Architecture des Plantes TA40/PSII, Boulevard de la Lironde 34398 MONTPELLIER CEDEX 5, France
tel : (33) 4 67 61 65 77 fax : (33) 4 67 61 56 68 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Iavor Diatchki
-
Pierre Barbier de Reuille