Proposal: Add isLeft/isRight to Data.Either

Herbert Valerio Riedel hvr at gnu.org
Thu Dec 6 12:41:51 CET 2012


"Bryan O'Sullivan" <bos at serpentine.com> writes:

> On Wed, Dec 5, 2012 at 8:16 AM, Henning Thielemann <
> lemming at 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



More information about the Libraries mailing list