Proposal: Add isLeft/isRight to Data.Either

Hi, I propose to add isLeft/isRight to Data.Either, with the obvious definitions: isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True There has been a discussion on that before [1]. While I agree that fromLeft/fromRight are moot, I don't see issues with isLeft/isRight. Personally I care mostly about isLeft, but for orthogonality I propose to add both isLeft and isRight. Here is a (possibly incomplete) list of packages that come with their own definition of isLeft: snap-core, multifocal, PriorityChansConverger, tamarin-prover-utils, Agda, PCLT, cmdtheline, scyther-proof, xmlhtml, hspec-expectations, Glob, language-glsl, Craft3e, hledger-lib, narc, nemesis, type-settheory, PCLT-DB, RJson, bio, errors, rss2irc, heist Discussion period: 2 Weeks Cheers, Simon [1] http://www.haskell.org/pipermail/libraries/2006-October/006098.html

+1 Excerpts from Simon Hengel's message of Fri Nov 30 12:38:59 -0800 2012:
Hi, I propose to add isLeft/isRight to Data.Either, with the obvious definitions:
isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False
isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True
There has been a discussion on that before [1]. While I agree that fromLeft/fromRight are moot, I don't see issues with isLeft/isRight.
Personally I care mostly about isLeft, but for orthogonality I propose to add both isLeft and isRight.
Here is a (possibly incomplete) list of packages that come with their own definition of isLeft:
snap-core, multifocal, PriorityChansConverger, tamarin-prover-utils, Agda, PCLT, cmdtheline, scyther-proof, xmlhtml, hspec-expectations, Glob, language-glsl, Craft3e, hledger-lib, narc, nemesis, type-settheory, PCLT-DB, RJson, bio, errors, rss2irc, heist
Discussion period: 2 Weeks
Cheers, Simon
[1] http://www.haskell.org/pipermail/libraries/2006-October/006098.html

+1
On Fri, Nov 30, 2012 at 3:38 PM, Simon Hengel
Hi, I propose to add isLeft/isRight to Data.Either, with the obvious definitions:
isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False
isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True
There has been a discussion on that before [1]. While I agree that fromLeft/fromRight are moot, I don't see issues with isLeft/isRight.
Personally I care mostly about isLeft, but for orthogonality I propose to add both isLeft and isRight.
Here is a (possibly incomplete) list of packages that come with their own definition of isLeft:
snap-core, multifocal, PriorityChansConverger, tamarin-prover-utils, Agda, PCLT, cmdtheline, scyther-proof, xmlhtml, hspec-expectations, Glob, language-glsl, Craft3e, hledger-lib, narc, nemesis, type-settheory, PCLT-DB, RJson, bio, errors, rss2irc, heist
Discussion period: 2 Weeks
Cheers, Simon
[1] http://www.haskell.org/pipermail/libraries/2006-October/006098.html
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

You can add lens to the list of packages that had to define their own (for
doctest purposes). ;)
On Fri, Nov 30, 2012 at 6:02 PM, Edward Kmett
+1
On Fri, Nov 30, 2012 at 3:38 PM, Simon Hengel
wrote: Hi, I propose to add isLeft/isRight to Data.Either, with the obvious definitions:
isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False
isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True
There has been a discussion on that before [1]. While I agree that fromLeft/fromRight are moot, I don't see issues with isLeft/isRight.
Personally I care mostly about isLeft, but for orthogonality I propose to add both isLeft and isRight.
Here is a (possibly incomplete) list of packages that come with their own definition of isLeft:
snap-core, multifocal, PriorityChansConverger, tamarin-prover-utils, Agda, PCLT, cmdtheline, scyther-proof, xmlhtml, hspec-expectations, Glob, language-glsl, Craft3e, hledger-lib, narc, nemesis, type-settheory, PCLT-DB, RJson, bio, errors, rss2irc, heist
Discussion period: 2 Weeks
Cheers, Simon
[1] http://www.haskell.org/pipermail/libraries/2006-October/006098.html
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Fri, Nov 30, 2012 at 6:48 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Fri, 30 Nov 2012, Edward Kmett wrote:
You can add lens to the list of packages that had to define their own
(for doctest purposes). ;)
I grepped for isLeft and isRight in lens-3.6 but did not find them.
It is used in Projection tests in the as yet unreleased 3.7 on github. src/Control/Lens/Projection.hs:-- >>> let isLeft (Left _) = True; isLeft _ = False -Edward

On Fri, 30 Nov 2012, Simon Hengel wrote:
Hi, I propose to add isLeft/isRight to Data.Either, with the obvious definitions:
isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False
isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True
There has been a discussion on that before [1]. While I agree that fromLeft/fromRight are moot, I don't see issues with isLeft/isRight.
Personally I care mostly about isLeft, but for orthogonality I propose to add both isLeft and isRight.
Here is a (possibly incomplete) list of packages that come with their own definition of isLeft:
snap-core, multifocal, PriorityChansConverger, tamarin-prover-utils, Agda, PCLT, cmdtheline, scyther-proof, xmlhtml, hspec-expectations, Glob, language-glsl, Craft3e, hledger-lib, narc, nemesis, type-settheory, PCLT-DB, RJson, bio, errors, rss2irc, heist
It would be a good opportunity to check how these packages use isLeft and isRight. E.g. if they use them in connection with fromLeft and fromRight then this would be an argument for me to exclude isLeft and isRight as well. cmdtheline uses these functions in test/Main.hs for checking whether command options could be parsed or not. Maybe the tests could be stricter if they do (Left expectedValue ==) or (Right expectedValue ==) instead. snap-core uses these functions once in test/suite/Snap/Core/Tests.hs for testing whether Left or Right is returned as expected. multifocal uses isLeft once in src/Language/XML/Xml2Type.hs: map (\(Left x) -> x) . filter isLeft Functions like maybeLeft :: Either a b -> Maybe a maybeRight :: Either a b -> Maybe b in connection with mapMaybe would be more helpful in this case, or just the existing 'Data.Either.lefts'. PriorityChansConverger defines isLeft, isRight, fromLeft, fromRight but does not use them anywhere. tamarin-prover-utils defines isLeft, isRight but does not use them anywhere. Agda uses isLeft and isRight in some QuickCheck properties. And then there is this application: do -- ps0 :: [NamedArg ParseLHS] ps0 <- mapM classPat ps let (ps1, rest) = span (isLeft . namedArg) ps0 (p2, ps3) <- uncons rest -- when (null rest): no field pattern or def pattern found guard $ all (isLeft . namedArg) ps3 let (f, lhs) = fromR p2 (ps', _:ps'') = splitAt (length ps1) ps return $ Right (f, LHSProj x ps' lhs ps'') Looks at least interesting ... :-) I get tired ... So far it seems that isLeft and isRight are frequently used in testing.

On 30.11.12 7:14 PM, Henning Thielemann wrote:
Agda uses isLeft and isRight in some QuickCheck properties. And then there is this application:
do -- ps0 :: [NamedArg ParseLHS] ps0 <- mapM classPat ps let (ps1, rest) = span (isLeft . namedArg) ps0 (p2, ps3) <- uncons rest -- when (null rest): no field pattern or def pattern found guard $ all (isLeft . namedArg) ps3 let (f, lhs) = fromR p2 (ps', _:ps'') = splitAt (length ps1) ps return $ Right (f, LHSProj x ps' lhs ps'')
Looks at least interesting ... :-)
Well, maybe this code could be improved, avoiding isLeft and fromR(ight). Basically, what I want to to here is: - I have a list of things: ps - I have a classification of these things into Left and Right: classPat - I want to succeed if exactly one of these things is classified as a Right - I want to extract that Right thing, modify it a bit: lhs - I want to obtain all the Left things unchanged: ps' and ps'' These standard functions do not do the job: - partitionEithers: loses the order of my things - lefts/rights: ditto The crux here is that the standard list functions like filter, span, break etc. use "Bool" as decision type. They would be more general with Either, using Left as falsehood and Right as truth. span :: (a -> Either b c) -> [a] -> ([c], [a]) break :: (a -> Either b c) -> [a] -> ([b], [a]) partition :: (a -> Either b c) -> [a] -> ([c], [b]) etc. How would you do it? Cheers, Andreas -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On 2 December 2012 08:42, Andreas Abel
On 30.11.12 7:14 PM, Henning Thielemann wrote:
Agda uses isLeft and isRight in some QuickCheck properties. And then there is this application:
do -- ps0 :: [NamedArg ParseLHS] ps0 <- mapM classPat ps let (ps1, rest) = span (isLeft . namedArg) ps0 (p2, ps3) <- uncons rest -- when (null rest): no field pattern or def pattern found guard $ all (isLeft . namedArg) ps3 let (f, lhs) = fromR p2 (ps', _:ps'') = splitAt (length ps1) ps return $ Right (f, LHSProj x ps' lhs ps'')
Looks at least interesting ... :-)
Well, maybe this code could be improved, avoiding isLeft and fromR(ight).
Basically, what I want to to here is: - I have a list of things: ps - I have a classification of these things into Left and Right: classPat - I want to succeed if exactly one of these things is classified as a Right - I want to extract that Right thing, modify it a bit: lhs - I want to obtain all the Left things unchanged: ps' and ps''
These standard functions do not do the job: - partitionEithers: loses the order of my things - lefts/rights: ditto
How do they lose the order? Or do you mean lose the order of "This Left is before that Right"?
The crux here is that the standard list functions like filter, span, break etc. use "Bool" as decision type. They would be more general with Either, using Left as falsehood and Right as truth.
span :: (a -> Either b c) -> [a] -> ([c], [a]) break :: (a -> Either b c) -> [a] -> ([b], [a]) partition :: (a -> Either b c) -> [a] -> ([c], [b])
Isn't your either-based partition function just partitionEithers?
etc.
How would you do it?
Cheers, Andreas
-- Andreas Abel <>< Du bist der geliebte Mensch.
Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY
andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

On 01.12.12 5:42 PM, Ivan Lazar Miljenovic wrote:
On 2 December 2012 08:42, Andreas Abel
wrote: On 30.11.12 7:14 PM, Henning Thielemann wrote:
Agda uses isLeft and isRight in some QuickCheck properties. And then there is this application:
do -- ps0 :: [NamedArg ParseLHS] ps0 <- mapM classPat ps let (ps1, rest) = span (isLeft . namedArg) ps0 (p2, ps3) <- uncons rest -- when (null rest): no field pattern or def pattern found guard $ all (isLeft . namedArg) ps3 let (f, lhs) = fromR p2 (ps', _:ps'') = splitAt (length ps1) ps return $ Right (f, LHSProj x ps' lhs ps'')
Looks at least interesting ... :-)
Well, maybe this code could be improved, avoiding isLeft and fromR(ight).
Basically, what I want to to here is: - I have a list of things: ps - I have a classification of these things into Left and Right: classPat - I want to succeed if exactly one of these things is classified as a Right - I want to extract that Right thing, modify it a bit: lhs - I want to obtain all the Left things unchanged: ps' and ps''
These standard functions do not do the job: - partitionEithers: loses the order of my things - lefts/rights: ditto
How do they lose the order? Or do you mean lose the order of "This Left is before that Right"?
Yes.
The crux here is that the standard list functions like filter, span, break etc. use "Bool" as decision type. They would be more general with Either, using Left as falsehood and Right as truth.
span :: (a -> Either b c) -> [a] -> ([c], [a]) break :: (a -> Either b c) -> [a] -> ([b], [a]) partition :: (a -> Either b c) -> [a] -> ([c], [b])
Isn't your either-based partition function just partitionEithers?
Yes.
How would you do it?
Cheers, Andreas
-- Andreas Abel <>< Du bist der geliebte Mensch.
Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY
andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On Sat, 1 Dec 2012, Andreas Abel wrote:
On 30.11.12 7:14 PM, Henning Thielemann wrote:
Agda uses isLeft and isRight in some QuickCheck properties. And then there is this application:
do -- ps0 :: [NamedArg ParseLHS] ps0 <- mapM classPat ps let (ps1, rest) = span (isLeft . namedArg) ps0 (p2, ps3) <- uncons rest -- when (null rest): no field pattern or def pattern found guard $ all (isLeft . namedArg) ps3 let (f, lhs) = fromR p2 (ps', _:ps'') = splitAt (length ps1) ps return $ Right (f, LHSProj x ps' lhs ps'')
Looks at least interesting ... :-)
Well, maybe this code could be improved, avoiding isLeft and fromR(ight).
Basically, what I want to to here is: - I have a list of things: ps - I have a classification of these things into Left and Right: classPat - I want to succeed if exactly one of these things is classified as a Right - I want to extract that Right thing, modify it a bit: lhs - I want to obtain all the Left things unchanged: ps' and ps''
Since you know that everything in ps' and ps'' is Left, I guess it would be more precise to return the value without the Left constructor, right?
These standard functions do not do the job: - partitionEithers: loses the order of my things - lefts/rights: ditto
right
The crux here is that the standard list functions like filter, span, break etc. use "Bool" as decision type. They would be more general with Either, using Left as falsehood and Right as truth.
span :: (a -> Either b c) -> [a] -> ([c], [a]) break :: (a -> Either b c) -> [a] -> ([b], [a])
Since you do not use the 'b' type in 'span' and the 'c' type in 'break' we would certainly prefer: spanMaybe :: (a -> Maybe c) -> [a] -> ([c], [a]) breakMaybe :: (a -> Maybe b) -> [a] -> ([b], [a]) However for your application, something with an Either "predicate" would be actually more appropriate. Like breakEither :: (a -> Either b c) -> [a] -> ([b], Maybe (c, [a]))
How would you do it?
E.g. I would try to avoid the irrefutable pattern (_:ps''), since it is a potential source of an error. For now I can only come up with a mix of explicit recursion and standard library functions (partitionEithers): import Data.Tuple.HT (mapFst) import Control.Monad (guard) import Data.Either (partitionEithers) breakEither :: (a -> Either b c) -> [a] -> ([b], Maybe (c, [a])) breakEither f = let go [] = ([], Nothing) go (e : es) = case f e of Left x -> mapFst (x :) $ go es Right x -> ([], Just (x, es)) in go splitAtSingleRight :: [Either a b] -> Maybe ([a], b, [a]) splitAtSingleRight xs = case breakEither id xs of (as, msuffix) -> do (c,es) <- msuffix case partitionEithers es of (ls, rs) -> guard (null rs) >> return (as, c, ls)

Simon Hengel
Hi, I propose to add isLeft/isRight to Data.Either, with the obvious definitions:
isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False
isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True
There has been a discussion on that before [1]. While I agree that fromLeft/fromRight are moot, I don't see issues with isLeft/isRight.
Personally I care mostly about isLeft, but for orthogonality I propose to add both isLeft and isRight.
+1 btw, what I've been missing even more than isLeft/isRight is something like leftMaybe :: Either a b -> Maybe a leftMaybe (Left x) = Just x leftMaybe _ = Nothing rightMaybe :: Either a b -> Maybe b rightMaybe (Right x) = Just x rightMaybe _ = Nothing cheers, hvr

On Tue, 4 Dec 2012, Herbert Valerio Riedel wrote:
btw, what I've been missing even more than isLeft/isRight is something like
leftMaybe :: Either a b -> Maybe a leftMaybe (Left x) = Just x leftMaybe _ = Nothing
rightMaybe :: Either a b -> Maybe b rightMaybe (Right x) = Just x rightMaybe _ = Nothing
These seem to be more useful for me than isLeft and isRight. However, I think I would prefer maybeLeft and maybeRight.

On 4 December 2012 22:04, Henning Thielemann
However, I think I would prefer maybeLeft and maybeRight.
I'd also prefer these names. I haven't had much use for any of these functions since I usually use custom types instead of Either, but I think they are obvious, simple and small functions, so I think it's a good idea to have them in the standard library rather than have everyone define their own version. +1 for isLeft/isRight, maybeLeft/maybeRight I'm not a fan of partial functions like fromLeft/fromRight. They lead to horrible error messages in current GHCs, so I would always write them as "let Left x = ... in ...". I'm not voting against them, but I'm also not voting for them, either. / Thomas

+1 for maybeLeft/maybeRight too
On Tue, Dec 4, 2012 at 11:04 PM, Henning Thielemann
On Tue, 4 Dec 2012, Herbert Valerio Riedel wrote:
btw, what I've been missing even more than isLeft/isRight is something like
leftMaybe :: Either a b -> Maybe a leftMaybe (Left x) = Just x leftMaybe _ = Nothing
rightMaybe :: Either a b -> Maybe b rightMaybe (Right x) = Just x rightMaybe _ = Nothing
These seem to be more useful for me than isLeft and isRight.
However, I think I would prefer maybeLeft and maybeRight.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Your ship was destroyed in a monadic eruption.

On 04.12.12 5:02 PM, Herbert Valerio Riedel wrote:
Simon Hengel
writes: Hi, I propose to add isLeft/isRight to Data.Either, with the obvious definitions:
isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False
isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True
There has been a discussion on that before [1]. While I agree that fromLeft/fromRight are moot, I don't see issues with isLeft/isRight.
Personally I care mostly about isLeft, but for orthogonality I propose to add both isLeft and isRight.
+1
btw, what I've been missing even more than isLeft/isRight is something like
leftMaybe :: Either a b -> Maybe a leftMaybe (Left x) = Just x leftMaybe _ = Nothing
rightMaybe :: Either a b -> Maybe b rightMaybe (Right x) = Just x rightMaybe _ = Nothing
I have not been missing these, but +1. -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

Hi Herbert, On Tue, Dec 04, 2012 at 11:02:07PM +0100, Herbert Valerio Riedel wrote:
btw, what I've been missing even more than isLeft/isRight is something like
leftMaybe :: Either a b -> Maybe a leftMaybe (Left x) = Just x leftMaybe _ = Nothing
rightMaybe :: Either a b -> Maybe b rightMaybe (Right x) = Just x rightMaybe _ = Nothing
There seems to be support for this. I think it would be useful to have a separate proposal/patch. Cheers, Simon

On Mittwoch, 5. Dezember 2012, 09:23:31, Simon Hengel wrote:
Hi Herbert,
On Tue, Dec 04, 2012 at 11:02:07PM +0100, Herbert Valerio Riedel wrote:
btw, what I've been missing even more than isLeft/isRight is something like
leftMaybe :: Either a b -> Maybe a leftMaybe (Left x) = Just x leftMaybe _ = Nothing
rightMaybe :: Either a b -> Maybe b rightMaybe (Right x) = Just x rightMaybe _ = Nothing
There seems to be support for this. I think it would be useful to have a separate proposal/patch.
I'm not against it, but I would like to ask whether these are really used so frequently that Prelude> :t either Just (const Nothing) either Just (const Nothing) :: Either a b -> Maybe a is too cumbersome.

On Wed, 5 Dec 2012, Daniel Fischer wrote:
On Mittwoch, 5. Dezember 2012, 09:23:31, Simon Hengel wrote:
Hi Herbert,
On Tue, Dec 04, 2012 at 11:02:07PM +0100, Herbert Valerio Riedel wrote:
btw, what I've been missing even more than isLeft/isRight is something like
leftMaybe :: Either a b -> Maybe a leftMaybe (Left x) = Just x leftMaybe _ = Nothing
rightMaybe :: Either a b -> Maybe b rightMaybe (Right x) = Just x rightMaybe _ = Nothing
There seems to be support for this. I think it would be useful to have a separate proposal/patch.
I'm not against it, but I would like to ask whether these are really used so frequently that
Prelude> :t either Just (const Nothing) either Just (const Nothing) :: Either a b -> Maybe a
is too cumbersome.
The same can be asked for Prelude> :t either (const False) (const True) either (const False) (const True) :: Either a b -> Bool or isLeft = isJust . maybeLeft

On Wed, Dec 5, 2012 at 8:16 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
The same can be asked for
Prelude> :t either (const False) (const True) either (const False) (const True) :: Either a b -> Bool
or
isLeft = isJust . maybeLeft
We at least have evidence that isLeft and isRight are actually present in several packages. That helps this proposal squeak over my bar, so I'm +0 on it. I think that maybeLeft and maybeRight are interesting, but the burden of proof for "these things solve a problem that actually exists" is a little higher. Consider me -0.01. In general, I feel we have a fondness for a few too many near-trivial one-liners that make libraries bigger and harder to navigate, without really adding much expressivity. For instance, aeson has a couple of combinators that are intended to help with structure access and lookup, and I've gotten pull requests for a bunch more due to the existing precedents, but they all have me feeling that the first few were wrong and the rest are even more wrong: they don't compose. Either lenses or a little DSL would have been better choices.

"Bryan O'Sullivan"
On Wed, Dec 5, 2012 at 8:16 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
The same can be asked for
Prelude> :t either (const False) (const True) either (const False) (const True) :: Either a b -> Bool
or
isLeft = isJust . maybeLeft
We at least have evidence that isLeft and isRight are actually present in several packages. That helps this proposal squeak over my bar, so I'm +0 on it.
I think that maybeLeft and maybeRight are interesting, but the burden of proof for "these things solve a problem that actually exists" is a little higher. Consider me -0.01.
In general, I feel we have a fondness for a few too many near-trivial one-liners that make libraries bigger and harder to navigate, without really adding much expressivity.
fair enough, here's some motivation why I think that maybe{Left,Right} might be worth to be added (and to some degree maybe even their co/dual counterparts): - maybe{Left,Right} compose points-free conveniently with existing Data.Maybe primitives, e.g. - lefts = mapMaybe maybeLeft - isLeft = isJust . maybeLeft - fromLeft' default = fromMaybe default . maybeLeft - fromRight' default = fromMaybe default . maybeRight - maybeRight is used in at least two packages (I didn't have time to search for more, but if it makes a difference, I'll search Hackage for more use cases): - precis:Precis.Utils.ControlOperators.suppress - errors:Control.Error.Util.hush and also their dual (see fromRight' above) is defined there: - precis:Precis.Utils.ControlOperators.elaborate - errors:Control.Error.Util.note - from{Left,Right} are useful when working in the 'Maybe' monad or applicative functor for converting 'Either'-typed values (this also applies to the dual case of working in the 'Either' monad/app-functor and having to deal with 'Maybe' values) - IMHO, 'maybeRight' has better readability than inlining 'either (const Nothing) Just' - for me it's not so much about typing less, as more about having code that is easier to read out loud. - I often use the 'when'-like combinator 'whenJust' in monadic code: whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) a = a x whenJust _ _ = return () or simply defined as a type specialized 'forM_': whenJust = Data.Foldable.forM_ then the argument about composability with 'Maybe' stated above applies (imho): do result <- try $ foobar whenJust (maybeLeft result) $ \e -> do putStrLn $ "warning: got error during shutdown:" putStrLn $ " " ++ e return () this way I can avoid having to use a 'case of' expression with an explicit '_ -> return ()' branch for which I always struggle a bit how to indent it: do result <- try $ foobar case result of Left e -> do putStrLn $ "warning: got error during shutdown: " putStrLn $ " " ++ e _ -> return () return () - As the types in Data.Either and Data.Maybe are part of the Haskell standard library, and IMHO basic primitives such as maybe{Left,Right} should be located in those modules as well. cheers, hvr

Herbert Valerio Riedel
and also their dual (see fromRight' above) is defined there:
sorry, I was mixed something up; ignore that "(see fromRight' above)" comment the dual to 'maybeRight' is rather something like: maybeToRight :: a -> Maybe b -> Either a b maybeToRight l = maybe (Left l) Right
- precis:Precis.Utils.ControlOperators.elaborate - errors:Control.Error.Util.note
- from{Left,Right} are useful when working in the 'Maybe' monad or
s/from/maybe/

+1 for Herberts proposal. On 06.12.12 6:41 AM, Herbert Valerio Riedel wrote:
- from{Left,Right} are useful when working in the 'Maybe' monad or applicative functor for converting 'Either'-typed values (this also applies to the dual case of working in the 'Either' monad/app-functor and having to deal with 'Maybe' values)
- IMHO, 'maybeRight' has better readability than inlining 'either (const Nothing) Just' - for me it's not so much about typing less, as more about having code that is easier to read out loud.
- I often use the 'when'-like combinator 'whenJust' in monadic code:
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) a = a x whenJust _ _ = return ()
+1. whenJust is defined also in Agda.Utils.Monad, should also added to Control.Monad.
- As the types in Data.Either and Data.Maybe are part of the Haskell standard library, and IMHO basic primitives such as maybe{Left,Right} should be located in those modules as well.
+1 -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

- I often use the 'when'-like combinator 'whenJust' in monadic code:
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) a = a x whenJust _ _ = return ()
+1. whenJust is defined also in Agda.Utils.Monad, should also added to Control.Monad.
Off topic, but I have whenJust in my local library too, and I use it all the time.

On 6 December 2012 23:05, Evan Laforge
- I often use the 'when'-like combinator 'whenJust' in monadic code:
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) a = a x whenJust _ _ = return ()
+1. whenJust is defined also in Agda.Utils.Monad, should also added to Control.Monad.
Off topic, but I have whenJust in my local library too, and I use it all the time.
In a project at work: $ grep -r whenJust --include=\*.hs . | wc -l 27

On Fri, Dec 7, 2012 at 9:29 AM, Bas van Dijk
On 6 December 2012 23:05, Evan Laforge
wrote: - I often use the 'when'-like combinator 'whenJust' in monadic code:
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) a = a x whenJust _ _ = return ()
+1. whenJust is defined also in Agda.Utils.Monad, should also added to Control.Monad.
Off topic, but I have whenJust in my local library too, and I use it all the time.
In a project at work:
$ grep -r whenJust --include=\*.hs . | wc -l 27
There is no need to define whenJust, since it is just a specialization of forM_ from Data.Foldable. Erik

On 7 December 2012 10:25, Erik Hesselink
On Fri, Dec 7, 2012 at 9:29 AM, Bas van Dijk
wrote: On 6 December 2012 23:05, Evan Laforge
wrote: - I often use the 'when'-like combinator 'whenJust' in monadic code:
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) a = a x whenJust _ _ = return ()
+1. whenJust is defined also in Agda.Utils.Monad, should also added to Control.Monad.
Off topic, but I have whenJust in my local library too, and I use it all the time.
In a project at work:
$ grep -r whenJust --include=\*.hs . | wc -l 27
There is no need to define whenJust, since it is just a specialization of forM_ from Data.Foldable.
Thanks for pointing this out! Replacing the 27 whenJusts as we speak... Bas

On 7 December 2012 10:49, Bas van Dijk
On 7 December 2012 10:25, Erik Hesselink
wrote: On Fri, Dec 7, 2012 at 9:29 AM, Bas van Dijk
wrote: On 6 December 2012 23:05, Evan Laforge
wrote: - I often use the 'when'-like combinator 'whenJust' in monadic code:
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenJust (Just x) a = a x whenJust _ _ = return ()
+1. whenJust is defined also in Agda.Utils.Monad, should also added to Control.Monad.
Off topic, but I have whenJust in my local library too, and I use it all the time.
In a project at work:
$ grep -r whenJust --include=\*.hs . | wc -l 27
There is no need to define whenJust, since it is just a specialization of forM_ from Data.Foldable.
Thanks for pointing this out! Replacing the 27 whenJusts as we speak...
hvr, I see you pointed this out earlier. Thanks.

On 7 December 2012 09:25, Erik Hesselink
There is no need to define whenJust, since it is just a specialization of forM_ from Data.Foldable.
I don't know if that's such a good argument. I prefer my code readable -- too much abstraction can have a seriously bad effect on that. As a simple rule, if the user has to do type inference in their head, readability suffers. In this case, "forM_" implies we're iterating over something container like, "whenJust" means "I want to do something if this thing yielded a result". It depends on the context whether a "Maybe" is behaving more container-like or is indicating the presence of a result where there may not have been one. / Thomas

On Friday, December 7, 2012, Thomas Schilling wrote:
On 7 December 2012 09:25, Erik Hesselink
javascript:;> wrote: There is no need to define whenJust, since it is just a specialization of forM_ from Data.Foldable.
I don't know if that's such a good argument. I prefer my code readable -- too much abstraction can have a seriously bad effect on that. As a simple rule, if the user has to do type inference in their head, readability suffers.
In this case, "forM_" implies we're iterating over something container like, "whenJust" means "I want to do something if this thing yielded a result". It depends on the context whether a "Maybe" is behaving more container-like or is indicating the presence of a result where there may not have been one.
I don't have this problem, but I guess that's just personal. But in general I'm not in favor of adding specialized versions of generalized functions. Erik

On Fri, 7 Dec 2012, Thomas Schilling wrote:
On 7 December 2012 09:25, Erik Hesselink
wrote: There is no need to define whenJust, since it is just a specialization of forM_ from Data.Foldable.
I don't know if that's such a good argument. I prefer my code readable -- too much abstraction can have a seriously bad effect on that. As a simple rule, if the user has to do type inference in their head, readability suffers.
In this case, "forM_" implies we're iterating over something container like, "whenJust" means "I want to do something if this thing yielded a result". It depends on the context whether a "Maybe" is behaving more container-like or is indicating the presence of a result where there may not have been one.
Too much abstraction can certainly reduce readability. In this case I interpret Maybe as a list that can contain at most one element. This way I can use all the nice functions from Data.Foldable for Maybe.

On 05/12/12 17:33, Bryan O'Sullivan wrote:
On Wed, Dec 5, 2012 at 8:16 AM, Henning Thielemann
mailto:lemming@henning-thielemann.de> wrote: The same can be asked for
Prelude> :t either (const False) (const True) either (const False) (const True) :: Either a b -> Bool
or
isLeft = isJust . maybeLeft
We at least have evidence that isLeft and isRight are actually present in several packages. That helps this proposal squeak over my bar, so I'm +0 on it.
I think that maybeLeft and maybeRight are interesting, but the burden of proof for "these things solve a problem that actually exists" is a little higher. Consider me -0.01.
I needed maybeRight just the other day, as a matter of fact. timeout n m | n < 0 = fmap Just m | n == 0 = return Nothing | otherwise = do r <- race (threadDelay n) m case r of Left _ -> return Nothing Right a -> return (Just a) would have been timeout n m | n < 0 = fmap Just m | n == 0 = return Nothing | otherwise = fmap maybeRight $ race (threadDelay n) m (I'd rather not use `either`, it's one of those functions whose type I always have to look up)
In general, I feel we have a fondness for a few too many near-trivial one-liners that make libraries bigger and harder to navigate, without really adding much expressivity.
I have a lot of sympathy for this view. Hence, only +0.3 from me. Cheers, Simon

On 10 December 2012 23:55, Simon Marlow
(I'd rather not use `either`, it's one of those functions whose type I always have to look up)
{-# LANGUAGE TypeSignatureRhymes #-} either :~: do something with the left or something with the right but either way give me something of the same type Conrad.

Simon Marlow
I needed maybeRight just the other day, as a matter of fact.
timeout n m | n < 0 = fmap Just m | n == 0 = return Nothing | otherwise = do r <- race (threadDelay n) m case r of Left _ -> return Nothing Right a -> return (Just a)
would have been
timeout n m | n < 0 = fmap Just m | n == 0 = return Nothing | otherwise = fmap maybeRight $ race (threadDelay n) m
(I'd rather not use `either`, it's one of those functions whose type I always have to look up)
Use (|||) from Control.Arrow instead. The thing on the left is applied to Lefts, the thing on the right to Rights.
In general, I feel we have a fondness for a few too many near-trivial one-liners that make libraries bigger and harder to navigate, without really adding much expressivity.
I have a lot of sympathy for this view. Hence, only
+0.3
and at most -1 from me, naturally. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
participants (18)
-
Andreas Abel
-
Bas van Dijk
-
Bryan O'Sullivan
-
Conrad Parker
-
Daniel Fischer
-
Edward Kmett
-
Edward Z. Yang
-
Erik Hesselink
-
Evan Laforge
-
Gábor Lehel
-
Henning Thielemann
-
Herbert Valerio Riedel
-
Ivan Lazar Miljenovic
-
John Wiegley
-
Jon Fairbairn
-
Simon Hengel
-
Simon Marlow
-
Thomas Schilling