simple-effects-0.12.0.0: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Early

Description

A neat effect that you can use to get early returns in your functions. Here's how to use it.

Before:

  f = do
      m1 <- maybeFunc1
      case m1 of
          Nothing -> return "1 nothing"
          Just x -> do
              m2 <- maybeFunc2
              case m2 of
                  Nothing -> return "2 nothing"
                  Just y -> return (x <> y)

After:

  f = handleEarly $ do
      m1 <- maybeFunc1
      x <- ifNothingEarlyReturn "1 nothing" m1
      m2 <- maybeFunc2
      y <- ifNothingEarlyReturn "2 nothing" m2
      return (x <> y)

You can use the earlyReturn function directly, or one of the helpers for common use cases.

Synopsis

Documentation

newtype Early a m Source #

Constructors

EarlyMethods 

Fields

Instances

Effect (Early a) Source # 

Associated Types

type CanLift (Early a :: (* -> *) -> *) (t :: (* -> *) -> * -> *) :: Constraint Source #

Methods

liftThrough :: (CanLift (Early a) t, Monad m, Monad (t m)) => Early a m -> Early a (t m) Source #

mergeContext :: Monad m => m (Early a m) -> Early a m Source #

type CanLift (Early a) t Source # 
type CanLift (Early a) t = MonadTrans t

earlyReturn :: forall a b m. MonadEffect (Early a) m => a -> m b Source #

Allows you to return early from a function. Make sure you handleEarly to get the actual result out.

handleEarly :: Monad m => ExceptT (EarlyValue a) m a -> m a Source #

Get the result from a computation. Either the early returned one, or the regular result.

onlyDo :: MonadEffect (Early a) m => m a -> m b Source #

Only do the given action and exit early with it's result.

ifNothingEarlyReturn :: MonadEffect (Early a) m => a -> Maybe b -> m b Source #

Early return the given value if the Maybe is Nothing. Otherwise, contnue with the value inside of it.

ifNothingDo :: MonadEffect (Early a) m => m a -> Maybe b -> m b Source #

Only do the given action and early return with it's result if the given value is Nothing. Otherwise continue with the value inside of the Maybe.

ifLeftEarlyReturn :: MonadEffect (Early c) m => (a -> c) -> Either a b -> m b Source #

If the value is a Left, get the value, process it and early return the result. Otherwise just return the Right value.

ifLeftDo :: MonadEffect (Early c) m => (a -> m c) -> Either a b -> m b Source #

If the value is a Left, get the value, process it and only do the resulting action. Otherwise just return the Right value.