from-sum-0.2.1.0: Canonical fromMaybeM and fromEitherM functions.

Copyright(c) Dennis Gosnell 2016
LicenseBSD-style (see LICENSE file)
Maintainercdep.illabout@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Control.FromSum

Contents

Description

This Haskell module exports various "from" functions for Either and Maybe.

Synopsis

Monadic in return value

fromEitherM :: Applicative m => (e -> m a) -> Either e a -> m a Source #

A monadic version of fromEither.

 fromEitherM leftAction === either leftAction pure
>>> fromEitherM (\s -> [length s]) $ Right 5
[5]
>>> fromEitherM (\s -> [length s]) $ Left ("foo" :: String)
[3]

fromEitherOrM :: Applicative m => Either e a -> (e -> m a) -> m a Source #

A fliped version of fromEitherM.

>>> fromEitherOrM (Right 5) $ \s -> [length s]
[5]

This can be nice to use as an error handler.

>>> fromEitherOrM (Right 5) $ \s -> putStrLn ("error: " ++ s) >> undefined
5
>>> fromEitherOrM (Left "foo") $ \s -> putStrLn ("error: " ++ s) >> undefined
error: foo
...

fromEitherM_ :: (Applicative m, Monoid b) => (e -> m b) -> Either e a -> m b Source #

Similar to fromEitherM, but only run the monadic leftAction if the Either argument is Left. Otherwise, return pure mempty.

 fromEitherM_ leftAction === either leftAction (const $ pure mempty)
>>> fromEitherM_ (\err -> putStrLn err >> pure "bye") $ Right 5
""
>>> fromEitherM_ (\err -> putStrLn err >> pure "bye") $ Left "there was an error"
there was an error
"bye"

This can be convenient when you want to run some sort of logging function whenever an Either is Left. If you imagine the logging function is b -> IO '()', then the effective type of fromEitherM_ becomes fromEitherM_ :: (e -> IO '()') -> Either e a -> IO '()', because '()' has a Monoid instance, and IO, has an Applicative instance.

>>> fromEitherM_ putStrLn $ Left "there was an error"
there was an error

fromEitherOrM_ :: (Applicative m, Monoid b) => Either e a -> (e -> m b) -> m b Source #

A fliped version of fromEitherM_.

fromMaybeM :: Applicative m => m a -> Maybe a -> m a Source #

A monadic version of fromMaybe.

 fromMaybeM nothingAction === maybe nothingAction pure
>>> fromMaybeM [] $ Just 5
[5]
>>> fromMaybeM [] Nothing
[]

fromMaybeOrM :: Applicative m => Maybe a -> m a -> m a Source #

A fliped version of fromMaybeM.

>>> fromMaybeOrM (Just 5) []
[5]

This can be nice to use as an error handler.

>>> fromMaybeOrM (Just 5) $ putStrLn "some error occurred" >> undefined
5
>>> fromMaybeOrM (Nothing) $ putStrLn "some error occurred" >> undefined
some error occurred
...

fromMaybeM_ :: (Applicative m, Monoid b) => m b -> Maybe a -> m b Source #

Similar to fromMaybeM, but only run the monadic nothingAction if the Maybe argument is Nothing. Otherwise, return pure mempty.

 fromMaybeM_ nothingAction === maybe nothingAction (const $ pure mempty)
>>> fromMaybeM_ (putStrLn "hello" >> pure "bye") $ Just 5
""
>>> fromMaybeM_ (putStrLn "hello" >> pure "bye") Nothing
hello
"bye"

This can be convenient when you want to run some sort of logging function whenever a Maybe is Nothing. If you imagine the logging function is IO '()', then the effective type of fromMaybeM_ becomes fromMaybeM_ :: IO '()' -> Maybe a -> IO '()', because '()' has a Monoid instance, and IO, has an Applicative instance.

>>> fromMaybeM_ (putStrLn "hello") Nothing
hello

fromMaybeOrM_ :: (Applicative m, Monoid b) => Maybe a -> m b -> m b Source #

A fliped version of fromMaybeM.

Monadic in both return and sum-type value

fromEitherMM :: Monad m => (e -> m a) -> m (Either e a) -> m a Source #

Similar to fromEitherM but the Either argument is also a monadic value.

>>> fromEitherMM (\s -> [length s]) [Right 5, Right 10]
[5,10]
>>> fromEitherMM (\s -> [length s]) [Left ("foo" :: String), Right 100]
[3,100]

NOTE: I don't particularly like the name of this function. If you have a suggestion for a better name, please submit a PR or issue.

fromEitherOrMM :: Monad m => m (Either e a) -> (e -> m a) -> m a Source #

A fliped version of fromEitherMM.

fromMaybeMM :: Monad m => m a -> m (Maybe a) -> m a Source #

Similar to fromMaybeM but the Maybe argument is also a monadic value.

>>> fromMaybeMM [] [Just 6, Just 5]
[6,5]
>>> fromMaybeMM [] [Just 6, Nothing, Just 7]
[6,7]

NOTE: I don't particularly like the name of this function. If you have a suggestion for a better name, please submit a PR or issue.

fromMaybeOrMM :: Monad m => m (Maybe a) -> m a -> m a Source #

A fliped version of fromMaybeMM.

Completely non-monadic functions

fromEither :: (e -> a) -> Either e a -> a Source #

Similar to fromMaybe.

>>> fromEither show $ Left 5
"5"
>>> fromEither show $ Right "hello"
"hello"

fromEitherOr :: Either e a -> (e -> a) -> a Source #

A fliped version of fromEither.

fromMaybe :: a -> Maybe a -> a #

The fromMaybe function takes a default value and and Maybe value. If the Maybe is Nothing, it returns the default values; otherwise, it returns the value contained in the Maybe.

Examples

Basic usage:

>>> fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>> fromMaybe "" Nothing
""

Read an integer from a string using readMaybe. If we fail to parse an integer, we want to return 0 by default:

>>> import Text.Read ( readMaybe )
>>> fromMaybe 0 (readMaybe "5")
5
>>> fromMaybe 0 (readMaybe "")
0

fromMaybeOr :: Maybe a -> a -> a Source #

A fliped version of fromMaybe.

Collapsing funtions

collapseEither :: Either a a -> a Source #

Collapse an Either a a to an a. Defined as fromEither id.

Note: Other libraries export this function as fromEither, but our fromEither function is slightly more general.

>>> collapseEither (Right 3)
3
>>> collapseEither (Left "hello")
"hello"

collapseExceptT :: Monad m => ExceptT a m a -> m a Source #

Similar to collapseEither, but for ExceptT.

>>> import Control.Monad.Except (ExceptT(ExceptT))
>>> collapseExceptT (ExceptT $ pure (Right 3))
3
>>> collapseExceptT (ExceptT $ pure (Left "hello"))
"hello"