[Haskell-cafe] Maybe to Either -- is there a better way?
Claude Heiland-Allen
claudiusmaximus at goto10.org
Tue Aug 3 14:33:13 EDT 2010
On 02/08/10 15:14, Tom Davies wrote:
> I find it convenient sometimes to convert a Maybe value to an Either thus (excuse the syntax, it's CAL, not Haskell):
>
> maybeToEither :: a -> Maybe b -> Either a b;
> maybeToEither errorValue = maybe (Left errorValue) (\x -> Right x);
>
> but that seemingly obvious function isn't in Hoogle, AFAICT, so perhaps there's some other approach?
I just uploaded djinn-th [1], a fork of Lennart Augustsson's djinn [2]
which uses TemplateHaskell to do things like:
{-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-}
import Language.Haskell.Djinn (djinnD)
$(djinnD "maybeToEither" [t|forall a b . a -> Maybe b -> Either a b|])
main = print . map (maybeToEither "foo") $ [Nothing, Just "bar"]
and get some results, if not always the one you intended.
[1] http://hackage.haskell.org/package/djinn-th
[2] http://hackage.haskell.org/package/djinn
Thanks,
Claude
--
http://claudiusmaximus.goto10.org
More information about the Haskell-Cafe
mailing list