Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Is it possible to access `WriterT`'s partially collected `tell`s in case of exception?

Tags:

haskell

Is it possible to have a WriterT monad that is able to share its partially collected tells in case of an exception? If I try outside of runWriterT the w seems to be discarded. If I try to try inside, I seem to need MonadUnliftIO. MonadUnliftIO sounds like it could help me, but that package says that it is only able to unlift monadic contexts and not monadic state which I guess Writer is. Has anyone done this with Writer or something similar?

Example pseudocode:

x <- runWriterT $ do
  result <- try $ do
    tell "a"
    tell "b"
    error "c"
    tell "d"
  case result of
    Left e -> Just e
    Right a -> Nothing

x `shouldBe` (Just "c", "ab")
like image 442
Wizek Avatar asked Apr 21 '19 20:04

Wizek


People also ask

How do you handle exceptions in DAO layer?

Every layer should have however their specific exceptions as generic. for example, DAO layer may have custom exception handlers like DavaSavingException, IOException etc.. So the approach is throw exception from DAO to service layer and again throw it to UI layer and catch in UI specific classes.

How do you handle exceptions in Robot Framework?

You can use TRY , EXCEPT , and FINALLY to catch and handle errors or exceptions. This is similar to handling exceptions in Python. See the TRY / EXCEPT / FINALLY exception catching and handling in Robot Framework article for more information.


2 Answers

Well, your code uses error. Morally speaking, all bets are off with error, because it signifies a bug in your program more than anything else. The fact that IO can catch the exceptions produced by it is really just an interesting quirk. Therefore, if you need this behavior, it's really best to use a proper exception monad transformer, like @Li-yaoXia recommends.

-- see Control.Monad.Except
action :: (MonadExcept String m, MonadWriter String m) =>
          m ()
action = do tell "a"
            tell "b"
            throwError "c"
            tell "d"

-- run action and massage it into your format
yourOutput :: (Maybe String, String)
yourOutput = runWriter $ fmap (either Just (const Nothing)) $ runExceptT actions

As to why error can't really work (at least, in a nice way), consider what error _ :: WriterT w m a actually means. error _ :: Int means "there is supposed to be a number here, but instead there's just a mistake." WriterT w m a is a type of program; the type of programs that keep of a log of type w, do some other stuff (m), and return a. Therefore, error _ :: WriterT w m a does not mean "a program that throws a recoverable error, preserving the log of type w," it means "there is supposed to be a program here, but instead there's just a mistake." Metaphorically speaking, the action psuedo-code you posted abruptly runs out of program, even though the type didn't mention that your program was allowed to suddenly terminate, and you should (metaphorically) thank your lucky stars that you are allowed to set up a replacement program (with try) rather than being properly chastised for the error!

With the ivory-towertop preaching out of the way, let's assume that we really do have

action :: MonadWriter String m => m ()
action = do tell "a"
            tell "b"
            error "c"
            tell "d"

and we just have to deal with it. Assuming you use the lazy version of Writer, you'll be happy to note that

runWriter action =
  ( ()
  , "a" ++ "b" ++ (case error "c" of (_, c) -> c) ++ "d"
  )

There exists this function that "salvages" a list by catching an impure exception (the immoral, "there is literally no program" kind I said error was) if it occurs while evaluating the spine.

-- can be recast as Free (a,) () -> IO (Free (a,) (Maybe e))
-- essentially, that type encodes the intuition that a list may end in [] (nil)
-- or in an error
salvageList :: Exception e => [a] -> IO ([a], Maybe e)
salvageList xs = catch (do xs' <- evaluate xs
                           case xs' of
                                [] -> return ([], Nothing)
                                (x : tl) -> do (tl', e) <- salvageList tl
                                               return (x : tl', e)
                       ) (\e -> return ([], Just e))

Which works:

-- we get the return value, too! that makes me feel... surprisingly weirded out!
yourOutputPlus :: IO ((), Maybe String, String)
yourOutputPlus = do let (val, log) = runWriter action
                    (realLog, error) <- salvageList log
                    return (val, fmap (\(ErrorCall msg) -> msg) error, realLog)
like image 162
HTNW Avatar answered Oct 18 '22 00:10

HTNW


If you want state to survive a runtime exception like this, your best bet is to use mutable variables. This is the approach we use inside Yesod, for example. The rio library has a MonadWriter instance based on mutable references that works this way:

#!/usr/bin/env stack
-- stack --resolver lts-13.17 script
{-# LANGUAGE NoImplicitPrelude #-}
import Test.Hspec
import RIO
import RIO.Writer

main = hspec $ it "writer and exceptions" $ do
  ref <- newSomeRef ""
  result <- tryAny $ runRIO ref $ do
    tell "a"
    tell "b"
    error "c"
    tell "d"
  case result of
    Left _ -> pure ()
    Right () -> error "it should have failed!!!"

  written <- readSomeRef ref
  written `shouldBe` "ab"

I touch on this (and related points) in my talk "Everything you didn't want to know about monad transformer state":

  • Slides: https://www.snoyman.com/reveal/monad-transformer-state
  • Video: https://www.youtube.com/watch?v=KZIN9f9rI34
like image 2
Michael Snoyman Avatar answered Oct 18 '22 00:10

Michael Snoyman