I went back and tried to convert the YAHT example to Monad, importing Monad,
commenting out all but the data descriptions and the searchAll function, and
finally replacing success, failure, augment, and combine in the searchAll
function with return, fail, >>=, and mplus.
*Main> let g = Graph [(1,'a'),(2,'b'),(3,'c'),(4,'d')]
[(1,2,'p'),(2,3,'q'),(1,4,'r'),(4,3,'s')]
*Main> searchAll g 1 3 :: [[Int]]
[[1,2,3],[1,4,3]]
*Main> searchAll g 1 3 :: Maybe [Int]
Just [1,2,3]
*Main> searchAll g 3 1 :: Maybe [Int]
Nothing
*Main> searchAll g 3 1 :: [[Int]]
[]
All good so far, but then tried to convert Failable from Computation to Monad
instance Monad Failable where
return = Success
fail = Fail
>>= (Success x) f = f x
>>= (Fail s) _ = Fail s
mplus (Fail _) y = y
mplus x _ = x
and got the following error.
Prelude> :l graph5
[1 of 1] Compiling Main ( graph5.hs, interpreted )
graph5.hs:34:4: parse error on input `>>='
Failed, modules loaded: none.
Prelude>
Complete code follows.
Michael
=========================
import Monad
data Failable a = Success a | Fail String deriving (Show)
data Graph v e = Graph [(Int,v)] [(Int,Int,e)]
{-
class Computation c where
success :: a -> c a
failure :: String -> c a
augment :: c a -> (a -> c b) -> c b
combine :: c a -> c a -> c a
instance Computation Maybe where
success = Just
failure = const Nothing
augment (Just x) f = f x
augment Nothing _ = Nothing
combine Nothing y = y
combine x _ = x
instance Computation Failable where
success = Success
failure = Fail
augment (Success x) f = f x
augment (Fail s) _ = Fail s
combine (Fail _) y = y
combine x _ = x
-}
instance Monad Failable where
return = Success
fail = Fail
>>= (Success x) f = f x
>>= (Fail s) _ = Fail s
mplus (Fail _) y = y
mplus x _ = x
{-
instance Computation [] where
success a = [a]
failure = const []
augment l f = concat (map f l)
combine = (++)
searchAll g@(Graph vl el) src dst
| src == dst = success [src]
| otherwise = search' el
where search' [] = failure "no path"
search' ((u,v,_):es)
| src == u = (searchAll g v dst `augment`
(success . (u:)))
`combine` search' es
| otherwise = search' es
-}
searchAll g@(Graph vl el) src dst
| src == dst = return [src]
| otherwise = search' el
where search' [] = fail "no path"
search' ((u,v,_):es)
| src == u = (searchAll g v dst >>=
(return . (u:)))
`mplus` search' es
| otherwise = search' es
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe