Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- onLeft :: Either a b -> (b -> c) -> (a -> c) -> c
- onRight :: Either a b -> (a -> c) -> (b -> c) -> c
- onJust :: Maybe a -> b -> (a -> b) -> b
- onNothing :: Maybe a -> (a -> b) -> b -> b
- onApp :: a -> (a -> b) -> b
- onMap :: Functor f => f a -> (a -> b) -> f b
- onExitSuccess :: ExitCode -> (Int -> b) -> b -> b
- onExitFailure :: ExitCode -> b -> (Int -> b) -> b
- onTrue :: Bool -> a -> a -> a
- onFalse :: Bool -> a -> a -> a
- onBiforFirst_ :: (Bifoldable t, Applicative f) => t a b -> (b -> f d) -> (a -> f c) -> f ()
- onBiforFirstM_ :: (Bifoldable t, Applicative f) => t a b -> (b -> f d) -> (a -> f c) -> f ()
- onBimapFirst :: Bifunctor t => t a c -> (c -> d) -> (a -> b) -> t b d
- onBimapSecond :: Bifunctor t => t a c -> (a -> b) -> (c -> d) -> t b d
- onBiforFirst :: (Bitraversable t, Applicative f) => t a b -> (b -> f d) -> (a -> f c) -> f (t c d)
- onBiforFirstM :: (Bitraversable t, Applicative f) => t a b -> (b -> f d) -> (a -> f c) -> f (t c d)
Introduction
overhang
provides convenience combinators for clean, "hanging" lambdas and depends only on base
. The gist of this library is offering variants of functions with parameter orders more conducive to finishing off the function call with a lambda. When using Data.Foldable
, sometimes we reach for for_
/ forM_
instead of traverse
/ mapM_
so we that can define the Applicative
/ Monad
computation right there in a lambda instead of making a separate function. That is the guiding principle of this library.
This package contains a single module and is intended to be imported qualified so that function intents are clear. The Getting Started section walks through a concrete example.
Getting Started
Suppose we need to do something with an Either String [Word16]
value:
main :: IO () main = do result <- readSamples someCd :: IO (Either String [Word16]) -- do some stuff...
We have a few choices. One choice is explicit pattern matching:
main :: IO () main = do result <- readSamples someCd :: IO (Either String [Word16]) case result of Left errString -> do putStrLn "R.I.P. to the CD, can't even play my hits!" putStrLn $ "Failure: " <> errString exitFailure Right samples -> playOnRepeat samples
Another option is to use the either
function from Data.Either
:
main :: IO () main = do result <- readSamples someCd :: IO (Either String [Word16]) either (\errString -> do putStrLn "R.I.P. to the CD, can't even play my hits!" putStrLn $ "Failure: " <> errString exitFailure) playOnRepeat result
We have gotten rid of explicit pattern matching, but the code doesn't exactly
look nice (subjective!), particularly in the handler for the Left
case.
A third option is to use the ExceptT
monad transformer:
main :: IO () main = do result <- runExceptT $ do samples <- ExceptT (readSamples someCd) :: ExceptT String IO [Word16] liftIO (playOnRepeat samples) -- Now what? We'll pattern match, but this feels like extra work... case result of Left errString -> do putStrLn "R.I.P. to the CD, can't even play my hits!" putStrLn $ "Failure: " <> errString exitFailure Right () -> pure ()
That was not super fun and arguably the least readable of all the examples so
far. For me, it is often the case when I'm processing an Either a b
value
that I have a teensy bit of work to do on one of the cases, and a bit more
work to do on the other case.
What if we switched the parameters around to either
and gave it a new name,
like onLeft
?
import qualified Overhang main :: IO () main = do result <- readSamples someCd :: IO (Either String [Word16]) Overhang.onLeft result playOnRepeat $ \errString -> do putStrLn "R.I.P. to the CD, can't even play my hits!" putStrLn $ "Failure: " <> errString exitFailure
Tada! We have gotten rid of explicit pattern matching just like we did with
either
, and depending on who you ask, the code is much more readable.
In the example, we were only dealing with a single Either
value. Sometimes
we have to deal with Either
s of Eithers
s, Either
s of Maybe
s and so on.
overhang
can help in these cases when we just want to neatly process the
structures and not pull in a large (but way more powerful!) dependency like
lens
.
Functions
Either
Maybe
Regular ol' Application
onApp :: a -> (a -> b) -> b Source #
Hang on function application, a.k.a. non-operator version of
&
.
onApp = (&)
Functor
onMap :: Functor f => f a -> (a -> b) -> f b Source #
Hang on a Functor
mapping function, a.k.a. non-operator version of
<&>
from lens
.
onMap = flip fmap
ExitCode
onExitSuccess :: ExitCode -> (Int -> b) -> b -> b Source #
Hang on the ExitSuccess
case of an ExitCode
. Mostly useful when b
is some
monadic computation.
onExitFailure :: ExitCode -> b -> (Int -> b) -> b Source #
Hang on the ExitFailure
case of an ExitCode
.
Bool
Bifoldable
onBiforFirst_ :: (Bifoldable t, Applicative f) => t a b -> (b -> f d) -> (a -> f c) -> f () Source #
Hang on the "left" folding portion of a Bifoldable
. A variant of bifor_
.
onBiforFirst_ t g f = bifor_ t f g
onBiforFirstM_ :: (Bifoldable t, Applicative f) => t a b -> (b -> f d) -> (a -> f c) -> f () Source #
Alias for onBiforFirst_
.
Bifunctor
onBimapFirst :: Bifunctor t => t a c -> (c -> d) -> (a -> b) -> t b d Source #
Hang on the "left" mapping portion of a Bifunctor
.
onBimapFirst t g f = bimap f g t
onBimapSecond :: Bifunctor t => t a c -> (a -> b) -> (c -> d) -> t b d Source #
Hang on the "right" mapping portion of a Bifunctor
.
onBimapSecond t f g = bimap f g t
Bitraversable
onBiforFirst :: (Bitraversable t, Applicative f) => t a b -> (b -> f d) -> (a -> f c) -> f (t c d) Source #
Hang on the "left" traversing portion of a Bitraversable
. A variant of bifor
.
onBiforFirst t g f = bifor t f g
onBiforFirstM :: (Bitraversable t, Applicative f) => t a b -> (b -> f d) -> (a -> f c) -> f (t c d) Source #
Alias for onBiforFirst
.