[Haskell-cafe] Either e Monad
Bas van Dijk
basvandijk at home.nl
Wed Sep 20 19:58:03 EDT 2006
On Tuesday 19 September 2006 09:40, Deokhwan Kim wrote:
> Albert Lai wrote:
> > Deokhwan Kim <dk at ropas.snu.ac.kr> writes:
> >> Where is the Monad instance declaration of Either e?
> >
> > It is in Control.Monad.Error as well. Strange: the doc doesn't state
> > it.
>
> Thanks a lot, Albert! I found the declaration in
> libraries/mtl/Control/Monad/Error.hs of the ghc source distribution:
>
> instance (Error e) => Monad (Either e) where
> return = Right
> Left l >>= _ = Left l
> Right r >>= k = k r
> fail msg = Left (strMsg msg)
I think I have a problem that can be solved by using Either as a Monad. In my
program I have the following function `update` which I would like to write
shorter:
type BoundVarsMap = [Binding]
type Binding = (Name, Maybe Exp)
type Name = String
data Exp = Var Name | App Exp Exp | Abs Name Exp | ...
-- update n e bvsMap returns Just the bvsMap where the first occurence of
-- (n, _) has been updated to (n, Just e). Nothing is returned if n was not
-- found in the bvsMap
update :: Name -> Exp -> BoundVarsMap -> Maybe BoundVarsMap
update _ _ [] = Nothing
update n e ((bn, me):bvsMap) | n == bn = Just ((bn, Just e):bvsMap)
| otherwise = update n e bvsMap >>=
return . ((bn, me):)
Example: update "b" (Var "z") [("a", Nothing), ("b", Nothing), ("c", Nothing)]
=> Just [("a",Nothing),("b",Just (Var "z")),("c",Nothing)]
Example: update "x" (Var "z") [("a", Nothing), ("b", Nothing), ("c", Nothing)]
=> Nothing
My question is: can I write `update` shorter by abstracting over the recursion
on the list?
I thought I could do it by somehow folding some function over the bvsMap which
encodes the n == bn case as Left ... and the otherwise case as Right ... Then
somehow using sequence to combine the resulting list. But I can't get it to
work.
It's late now here in Holland (~02:00) and I'm losing my concentration ;-) So
I will just ask if somebody knows a shorter version.
Thanks,
Bas van Dijk
More information about the Haskell-Cafe
mailing list