garlic-bread-0.1.0.1: A monad transformer for keeping track of where you've come from.

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Bread

Description

Sometimes you need to care about the path you take.

Suppose you're parsing some data -- you're likely using the Either type to keep track of errors. This is good!

Unfortunately, sometimes you have weird nested data, and then when you go to parse, you get this back:

Left (IntParseError "c")

Now, you're left wondering: "Where is that c? How did it get there? How can I minimally reproduce this?" And unfortunately, all of the context is lost: the error has been thrown from deep in the stack, and you're stuck munging around in the source data.

When you're dealing with some deeply nested data that might fail, you're left wondering: How do I get there from here? Let's leave breadcrumbs along the way, so that we can find our way back!

Suppose you're trying to find a specific value in a deeply nested data structure. You can use Bread to lay breadcrumbs and then exit as soon as you've found what you need, collecting the breadcrumbs along the way.

Synopsis

Documentation

newtype BreadT crumb exit m a Source #

BreadT is a monad transformer that allows you to leave breadcrumbs of types crumb while you're performing some effects on the underlying monad m. If you want to exit early, then exit early will end up returning a Left (crumbs, early), where crumbs is a list of all breadcrumbs that you've left so far.

Since: 0.1.0.0

Constructors

BreadT 

Fields

Instances

MonadWriter w m => MonadWriter w (BreadT crumb exit m) Source # 

Methods

writer :: (a, w) -> BreadT crumb exit m a #

tell :: w -> BreadT crumb exit m () #

listen :: BreadT crumb exit m a -> BreadT crumb exit m (a, w) #

pass :: BreadT crumb exit m (a, w -> w) -> BreadT crumb exit m a #

MonadState s m => MonadState s (BreadT crumb exit m) Source # 

Methods

get :: BreadT crumb exit m s #

put :: s -> BreadT crumb exit m () #

state :: (s -> (a, s)) -> BreadT crumb exit m a #

MonadReader r m => MonadReader r (BreadT crumb exit m) Source #

The MonadReader instance for BreadT delegates to the underlying instance for m.

Methods

ask :: BreadT crumb exit m r #

local :: (r -> r) -> BreadT crumb exit m a -> BreadT crumb exit m a #

reader :: (r -> a) -> BreadT crumb exit m a #

Monad m => MonadError exit (BreadT crumb exit m) Source #

The MonadError instance for BreadT gathers the crumbotations collected so far, and throws the exception paired with the crumbotations.

Methods

throwError :: exit -> BreadT crumb exit m a #

catchError :: BreadT crumb exit m a -> (exit -> BreadT crumb exit m a) -> BreadT crumb exit m a #

MonadTrans (BreadT crumb exit) Source # 

Methods

lift :: Monad m => m a -> BreadT crumb exit m a #

Monad m => Monad (BreadT crumb exit m) Source # 

Methods

(>>=) :: BreadT crumb exit m a -> (a -> BreadT crumb exit m b) -> BreadT crumb exit m b #

(>>) :: BreadT crumb exit m a -> BreadT crumb exit m b -> BreadT crumb exit m b #

return :: a -> BreadT crumb exit m a #

fail :: String -> BreadT crumb exit m a #

Functor m => Functor (BreadT crumb exit m) Source # 

Methods

fmap :: (a -> b) -> BreadT crumb exit m a -> BreadT crumb exit m b #

(<$) :: a -> BreadT crumb exit m b -> BreadT crumb exit m a #

Monad m => Applicative (BreadT crumb exit m) Source # 

Methods

pure :: a -> BreadT crumb exit m a #

(<*>) :: BreadT crumb exit m (a -> b) -> BreadT crumb exit m a -> BreadT crumb exit m b #

liftA2 :: (a -> b -> c) -> BreadT crumb exit m a -> BreadT crumb exit m b -> BreadT crumb exit m c #

(*>) :: BreadT crumb exit m a -> BreadT crumb exit m b -> BreadT crumb exit m b #

(<*) :: BreadT crumb exit m a -> BreadT crumb exit m b -> BreadT crumb exit m a #

MonadIO m => MonadIO (BreadT crumb exit m) Source # 

Methods

liftIO :: IO a -> BreadT crumb exit m a #

runBreadT :: BreadT crumb exit m a -> m (Either ([crumb], exit) a) Source #

Unwrap the BreadT part of a monad transformer stack. The return type contains Either a pair of the breadcrumbs and the thrown error, or the result value.

Since: 0.1.0.0

type Bread crumb exit = BreadT crumb exit Identity Source #

A monad that can collect breadcrumbs and exit early with them, but do nothing else.

Since: 0.1.0.0

runBread :: Bread crumb exit a -> Either ([crumb], exit) a Source #

Run a Bread computation, returning either a pair of the breadcrumbs and error or a successful result.

Since: 0.1.0.0

withCrumb :: Monad m => crumb -> BreadT crumb exit m a -> BreadT crumb exit m a Source #

Lay a breadcrumb, so you'll know where you came from.

>>> runBread (withCrumb 'a' (exit "Nope"))
Left ("a", "Nope")

Since: 0.1.0.0

exit :: Monad m => exit -> BreadT crumb exit m a Source #

Short circuit the BreadT computation. This causes the computation to exit with the provided exit value and the crumbs collected along the way.

Since: 0.1.0.0

handleExit :: Monad m => BreadT crumb exit m a -> (exit -> BreadT crumb exit m a) -> BreadT crumb exit m a Source #

Sometimes, a BreadT computation short-circuits with an exit, but you don't want it to exit just yet -- perhaps you want to take a different path. This function lets you handle exit and potentially choose a different path.

withCrumb 1 $ do
     exit "I'm tired"
         handleExit reason ->
             pure "No, let's persevere!"

Since: 0.1.0.0

crumbs :: Monad m => BreadT crumb exit m [crumb] Source #

Return the current collection of crumbs collected thus far.

Since: 0.1.0.0