| Safe Haskell | None |
|---|
System.Log.Raven.Scotty
Description
Utilities to log errors in Scotty actions using raven-haskell.
import Web.Scotty
import System.Log.Raven
import System.Log.Raven.Transport.HttpConduit (sendRecord)
import System.Log.Raven.Scotty
main = do
raven <- initRaven "https://…" id sendRecord stderrFallback
let hereBeDragons = guardIO raven "my.logger" (Just "DragonsError") (Just "My.Inner.Dragons")
scotty 8000 $ do
post "/some/action/" $ do
arg1 <- param "arg1"
arg2 <- param "arg2"
ds <- hereBeDragons $ dragonsIO arg1 arg2
if null ds
then text "no dragons"
else do
let msg = "dragons! run!"
scottyHttpInterface >>= logError raven "Main.main" msg
- guardIO :: SentryService -> String -> Maybe String -> Maybe String -> IO a -> ActionM a
- logError :: SentryService -> String -> String -> (SentryRecord -> SentryRecord) -> ActionM ()
- scottyHttpInterface :: ActionM (SentryRecord -> SentryRecord)
Documentation
Arguments
| :: SentryService | Configured Sentry service. |
| -> String | Logger name. |
| -> Maybe String | Exception type name. |
| -> Maybe String | Action module name. |
| -> IO a | Action to run. |
| -> ActionM a | Result in a Scotty ActionM monad. |
A liftIO alternative that logs unhandled exceptions. The function itself is verbose in arguments and designed to be curried and reused.
Arguments
| :: SentryService | A configured Sentry service. |
| -> String | Logger name. |
| -> String | Message to log. |
| -> (SentryRecord -> SentryRecord) | Additional interfaces or other updates. |
| -> ActionM () |
Log an error in an ActionM monad, collecting request data.
scottyHttpInterface :: ActionM (SentryRecord -> SentryRecord)Source
Collect request parameters for a HTTP sentry interface.