module App.Behaviours.Exception where
import Data.List (filter)
import Control.Applicative
import qualified Control.Exception as Ex
import App.EventBus
import Text.PrettyPrint
import qualified Data.Set as Set
import System.IO
import Data.Time
import System.Locale
renderException (Event nm _ _ edata source tm) =
brackets (text (formatTime defaultTimeLocale "%T" tm)) <+> text "Exception thrown from" <+> text source <> colon <+> text nm $+$
(nest 4 . vcat . map text . map (safeShow (Just 80)) $ edata)
unhandledExceptionBehaviour :: Behaviour [EData a]
unhandledExceptionBehaviour b = consumeEventGroupCollectivelyWith b "Exception" $
(return []) <$ (Ex.throwIO . Ex.ErrorCall . render . vcat . map renderException . Set.toList)
disregardExceptionsFromSource :: String -> Behaviour [EData a]
disregardExceptionsFromSource s b = pollEventGroupWith b "Exception" $
(\e -> return $ if src e == s then [Deletion e] else [])
disregardExceptionsNamed :: String -> Behaviour [EData a]
disregardExceptionsNamed n b = pollEventGroupWith b "Exception" $
(\e -> return $ if ename e == n then [Deletion e] else [])
printAndDisregardExceptionsFromSource :: String -> Behaviour [EData a]
printAndDisregardExceptionsFromSource s b = pollEventGroupWith b "Exception" $ \e ->
if src e == s then (return . return $ [Deletion e]) =<< (putStrLn . render . renderException $ e) else return []
printAndDisregardExceptionsNamed :: String -> Behaviour [EData a]
printAndDisregardExceptionsNamed n b = pollEventGroupWith b "Exception" $ \e ->
if ename e == n then (return . return $ [Deletion e]) =<< (putStrLn . render . renderException $ e) else return []
logAndDisregardExceptionsFromSource :: Handle -> String -> Behaviour [EData a]
logAndDisregardExceptionsFromSource h s b = pollEventGroupWith b "Exception" $ \e ->
if src e == s then (return . return $ [Deletion e]) =<< (hPutStrLn h . render . renderException $ e) else return []
logAndDisregardExceptionsNamed :: Handle -> String -> Behaviour [EData a]
logAndDisregardExceptionsNamed h n b = pollEventGroupWith b "Exception" $ \e ->
if ename e == n then (return . return $ [Deletion e]) =<< (hPutStrLn h . render . renderException $ e) else return []