[Haskell-cafe] Fail-back monad
Alberto G. Corona
agocorona at gmail.com
Wed Mar 28 11:26:44 CEST 2012
Sorry, the text example again without HTML formatting:
test= runBackT $ do
lift $ print "will not return back here"
liftBackPoint $ print "will return here"
n2 <- lift $ getLine
lift $ print "second input"
n3 <- lift $ getLine
if n3 == "back"
then fail ""
else lift $ print $ n2++n3
I wrote a blog entry about this :
http://haskell-web.blogspot.com.es/2012/03/failback-monad.html
2012/3/28 Alberto G. Corona <agocorona at gmail.com>:
> Hi Haskellers.
>
> In my package MFlow [1] I program an entire web navigation in a
> single procedure. That happened in the good-old WASH web application
> framework.
> The problem is the back button in the Browser.
> To go back in the code to the previous interactions when the data
> input does not match the expected because the user pressed the back
> button one or more times, i came across this Monad specimen,: that
> solves the problem.
>
>
> data FailBack a = BackPoint a -- will go back to this point
> | NoBack a . -- Normal outcome
> | GoBack -- "exception":: must
> go to the last backPoint
>
> newtype BackT m a = BackT { runBackT :: m (FailBack a ) }
>
> -- this monad nas a loop
>
> instance Monad m => Monad (BackT m) where
> fail _ = BackT $ return GoBack
> return x = BackT . return $ NoBack x
> x >>= f = BackT $ loop
> where
> loop = do
> v <- runBackT x
> case v of
> NoBack y -> runBackT (f y) -- business as usual
> BackPoint y -> do
> z <- runBackT (f y)
> case z of
> GoBack -> loop -- if x was a backpoint,
> then redirects the flow to this backpoint
> other -> return other
> GoBack -> return GoBack --propagate the signal back
>
>
> This monad does not perform exploration of alternatives as is the
> case of MonadPlus instances. It does not perform the kind of
> backtracking of "nondeterministic" three navigations in the Prolog
> style. It just go back to the last point where the computation can
> restart again in a sequence of actions.
>
> In this example:
>
>
> liftBackPoint f= BackT $ f >>= \x -> return $ BackPoint x
>
> test= runBackT $ do
> lift $ print "will not return back here"
> liftBackPoint $ print "will return here"
> n2 <- lift $ getLine
> lift $ print "second input"
> n3 <- lift $ getLine
> if n3 == "back"
> then fail ""
> else lift $ print $ n2++n3
>
> Whenever the second input is "back" The procedure will go back to
> where liftBackPoint is. Otherwise, it will return the concatenation of
> the two inputs. If the underlying monad is an instance of MonadState,
> it can transport the state that caused the failure to the backpoint.
>
> Are there something similar? May it be functionally equivalent to
> something simpler or with more grounds?
> I looked at some exception monads out there, but they did not seems
> to share the same idea
>
> [1] http://haskell-web.blogspot.com.es/2012/02/web-application-server-with-stateful.html
More information about the Haskell-Cafe
mailing list