Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-04 Thread Henning Thielemann
Ivan Lazar Miljenovic schrieb: Yitzchak Gale g...@sefer.org writes: While useful, I think its ubiquity to simplicity ratio is not high enough to justify either depending on MissingH just for that, or adding it to a base library. Just like the swap :: (a,b) - (b,a) function a lot of people

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-04 Thread Alexander Dunlap
On Wed, Aug 4, 2010 at 9:21 AM, Henning Thielemann schlepp...@henning-thielemann.de wrote: Ivan Lazar Miljenovic schrieb: Yitzchak Gale g...@sefer.org writes: While useful, I think its ubiquity to simplicity ratio is not high enough to justify either depending on MissingH just for that, or

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-04 Thread Max Rabkin
On Tue, Aug 3, 2010 at 8:33 PM, Claude Heiland-Allen claudiusmaxi...@goto10.org wrote: {-# 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) $

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-04 Thread Christopher Done
On 4 August 2010 18:40, Alexander Dunlap alexander.dun...@gmail.com wrote: It's also nice for people reading code if common functions are functions from common libraries. This allows readers' vocabulary of common functions to increase, so they don't have to trawl through someone's personal

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-03 Thread Yitzchak Gale
Tom Davies wrote: I find it convenient sometimes to convert a Maybe value to an Either maybeToEither = flip maybe Right . Left Christopher Done wrote: It's available in MissingH While useful, I think its ubiquity to simplicity ratio is not high enough to justify either depending on MissingH

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-03 Thread Ivan Lazar Miljenovic
Yitzchak Gale g...@sefer.org writes: Tom Davies wrote: I find it convenient sometimes to convert a Maybe value to an Either maybeToEither = flip maybe Right . Left Remember, some people don't like flip! :p maybeToEither = (`maybe` Right) . Left While useful, I think its ubiquity to

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-03 Thread Yitzchak Gale
I wrote: maybeToEither = flip maybe Right . Left Ivan Lazar Miljenovic wrote: Remember, some people don't like flip! :p maybeToEither = (`maybe` Right) . Left Yes, absolutely! ...go ahead and upload it to Hackage Just give it a good name, rather than fooToolkit, barToolkit, etc. How

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-03 Thread Claude Heiland-Allen
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

[Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-02 Thread Tom Davies
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

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-02 Thread Christopher Done
It's available in MissingH: http://hackage.haskell.org/packages/archive/MissingH/latest/doc/html/Data-Either-Utils.html#v:maybeToEither You can find this using Hayoo, which indexes Hackage. MissingH is pretty huge, though, just for one function. It's kind of annoying. I'm using this function in