[Haskell-cafe] Missing a "Deriving"?
Ross Mellgren
rmm-haskell at z.odi.ac
Mon Jun 1 21:43:34 EDT 2009
Oh I wasn't clear -- you need multiple instance declarations for a
given type (Failable, for example), one for each type class you're
implementing.
That is,
instance Monad Failable where
return = ...
...
instance MonadPlus Failable where
mplus = ...
...
-Ross
On Jun 1, 2009, at 9:40 PM, michael rice wrote:
> Hi Ross,
>
> I thought of that, but return, fail, and >>= became "not visible"
> when I changed the instance declaration from Monad to MonadPlus..
> Can Failable be in two instance declarations, one for Monad (giving
> it return, fail, and >>=) and one for MonadPlus (giving it mplus)?
>
> Michael
>
> --- On Mon, 6/1/09, Ross Mellgren <rmm-haskell at z.odi.ac> wrote:
>
> From: Ross Mellgren <rmm-haskell at z.odi.ac>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: "michael rice" <nowgate at yahoo.com>
> Cc: "haskell-cafe Cafe" <haskell-cafe at haskell.org>
> Date: Monday, June 1, 2009, 9:33 PM
>
> mplus is a method of class MonadPlus, so you need to write it in a
> separate instance from the one for Monad, e.g.
>
> instance MonadPlus Failable where
> mplus = ...
>
> -Ross
>
> On Jun 1, 2009, at 9:28 PM, michael rice wrote:
>
>> Still stumped. Maybe and [] are in the same MonadPlus monad, but
>> how do I make monad Failable understand mplus?
>>
>> I'm now getting this error upon loading:
>>
>>
>> Prelude> :l graph5
>> [1 of 1] Compiling Main ( graph5.hs, interpreted )
>>
>> graph5.hs:36:4: `mplus' is not a (visible) method of class `Monad'
>> 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
>>
>>
>>
>> -----Inline Attachment Follows-----
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090601/59913874/attachment.html
More information about the Haskell-Cafe
mailing list