module Network.Bugsnag.Notify ( notifyBugsnag , notifyBugsnagWith ) where import Prelude import Control.Exception (SomeException, fromException, toException) import qualified Control.Exception as Exception import Control.Exception.Annotated (AnnotatedException) import qualified Control.Exception.Annotated as Annotated import Control.Monad (unless, (<=<)) import Data.Annotation (tryAnnotations) import Data.Bugsnag import Data.Bugsnag.Settings import Data.Foldable (fold) import Data.List.NonEmpty (nonEmpty) import Network.Bugsnag.BeforeNotify import Network.Bugsnag.Exception import Network.Bugsnag.MetaData import Network.HTTP.Client.TLS (getGlobalManager) notifyBugsnag :: Exception.Exception e => Settings -> e -> IO () notifyBugsnag :: forall e. Exception e => Settings -> e -> IO () notifyBugsnag = BeforeNotify -> Settings -> e -> IO () forall e. Exception e => BeforeNotify -> Settings -> e -> IO () notifyBugsnagWith BeforeNotify forall a. Monoid a => a mempty notifyBugsnagWith :: Exception.Exception e => BeforeNotify -> Settings -> e -> IO () notifyBugsnagWith :: forall e. Exception e => BeforeNotify -> Settings -> e -> IO () notifyBugsnagWith BeforeNotify f Settings settings = Settings -> Event -> IO () reportEvent Settings settings (Event -> IO ()) -> (e -> Event) -> e -> IO () forall b c a. (b -> c) -> (a -> b) -> a -> c . BeforeNotify -> e -> Event forall e. Exception e => BeforeNotify -> e -> Event buildEvent BeforeNotify bn where bn :: BeforeNotify bn = BeforeNotify f BeforeNotify -> BeforeNotify -> BeforeNotify forall a. Semigroup a => a -> a -> a <> Settings -> BeforeNotify globalBeforeNotify Settings settings reportEvent :: Settings -> Event -> IO () reportEvent :: Settings -> Event -> IO () reportEvent Settings {[Text] Maybe Text Maybe CodeIndex Text ApiKey BeforeNotify Exception -> Bool HttpException -> IO () settings_apiKey :: ApiKey settings_appVersion :: Maybe Text settings_releaseStage :: Text settings_enabledReleaseStages :: [Text] settings_beforeNotify :: BeforeNotify settings_ignoreException :: Exception -> Bool settings_onNotifyException :: HttpException -> IO () settings_codeIndex :: Maybe CodeIndex settings_apiKey :: Settings -> ApiKey settings_appVersion :: Settings -> Maybe Text settings_releaseStage :: Settings -> Text settings_enabledReleaseStages :: Settings -> [Text] settings_beforeNotify :: Settings -> BeforeNotify settings_ignoreException :: Settings -> Exception -> Bool settings_onNotifyException :: Settings -> HttpException -> IO () settings_codeIndex :: Settings -> Maybe CodeIndex ..} Event event = Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless ([Exception] -> Bool forall a. [a] -> Bool forall (t :: * -> *) a. Foldable t => t a -> Bool null ([Exception] -> Bool) -> [Exception] -> Bool forall a b. (a -> b) -> a -> b $ Event -> [Exception] event_exceptions Event event) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ do Manager m <- IO Manager getGlobalManager Either HttpException () result <- Manager -> ApiKey -> [Event] -> IO (Either HttpException ()) sendEvents Manager m ApiKey settings_apiKey [Event event] (HttpException -> IO ()) -> (() -> IO ()) -> Either HttpException () -> IO () forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either HttpException -> IO () settings_onNotifyException () -> IO () forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure Either HttpException () result buildEvent :: Exception.Exception e => BeforeNotify -> e -> Event buildEvent :: forall e. Exception e => BeforeNotify -> e -> Event buildEvent BeforeNotify bn e e = BeforeNotify -> e -> Event -> Event forall e. Exception e => BeforeNotify -> e -> Event -> Event runBeforeNotify BeforeNotify bn e e (Event -> Event) -> Event -> Event forall a b. (a -> b) -> a -> b $ Event defaultEvent { event_exceptions = [ex] , event_metaData = unMetaData <$> metaDataFromException e } where ex :: Exception ex = SomeException -> Exception bugsnagExceptionFromSomeException (SomeException -> Exception) -> SomeException -> Exception forall a b. (a -> b) -> a -> b $ e -> SomeException forall e. Exception e => e -> SomeException Exception.toException e e metaDataFromException :: Exception.Exception e => e -> Maybe MetaData metaDataFromException :: forall e. Exception e => e -> Maybe MetaData metaDataFromException = AnnotatedException SomeException -> Maybe MetaData forall e. AnnotatedException e -> Maybe MetaData metaDataFromAnnotatedException (AnnotatedException SomeException -> Maybe MetaData) -> (e -> Maybe (AnnotatedException SomeException)) -> e -> Maybe MetaData forall (m :: * -> *) b c a. Monad m => (b -> m c) -> (a -> m b) -> a -> m c <=< (forall e. Exception e => SomeException -> Maybe e fromException @(AnnotatedException SomeException) (SomeException -> Maybe (AnnotatedException SomeException)) -> (e -> SomeException) -> e -> Maybe (AnnotatedException SomeException) forall b c a. (b -> c) -> (a -> b) -> a -> c . e -> SomeException forall e. Exception e => e -> SomeException toException) metaDataFromAnnotatedException :: AnnotatedException e -> Maybe MetaData metaDataFromAnnotatedException :: forall e. AnnotatedException e -> Maybe MetaData metaDataFromAnnotatedException = (NonEmpty MetaData -> MetaData) -> Maybe (NonEmpty MetaData) -> Maybe MetaData forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap NonEmpty MetaData -> MetaData forall m. Monoid m => NonEmpty m -> m forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m fold (Maybe (NonEmpty MetaData) -> Maybe MetaData) -> (AnnotatedException e -> Maybe (NonEmpty MetaData)) -> AnnotatedException e -> Maybe MetaData forall b c a. (b -> c) -> (a -> b) -> a -> c . [MetaData] -> Maybe (NonEmpty MetaData) forall a. [a] -> Maybe (NonEmpty a) nonEmpty ([MetaData] -> Maybe (NonEmpty MetaData)) -> (AnnotatedException e -> [MetaData]) -> AnnotatedException e -> Maybe (NonEmpty MetaData) forall b c a. (b -> c) -> (a -> b) -> a -> c . ([MetaData], [Annotation]) -> [MetaData] forall a b. (a, b) -> a fst (([MetaData], [Annotation]) -> [MetaData]) -> (AnnotatedException e -> ([MetaData], [Annotation])) -> AnnotatedException e -> [MetaData] forall b c a. (b -> c) -> (a -> b) -> a -> c . [Annotation] -> ([MetaData], [Annotation]) forall a. Typeable a => [Annotation] -> ([a], [Annotation]) tryAnnotations ([Annotation] -> ([MetaData], [Annotation])) -> (AnnotatedException e -> [Annotation]) -> AnnotatedException e -> ([MetaData], [Annotation]) forall b c a. (b -> c) -> (a -> b) -> a -> c . AnnotatedException e -> [Annotation] forall exception. AnnotatedException exception -> [Annotation] Annotated.annotations globalBeforeNotify :: Settings -> BeforeNotify globalBeforeNotify :: Settings -> BeforeNotify globalBeforeNotify Settings {[Text] Maybe Text Maybe CodeIndex Text ApiKey BeforeNotify Exception -> Bool HttpException -> IO () settings_apiKey :: Settings -> ApiKey settings_appVersion :: Settings -> Maybe Text settings_releaseStage :: Settings -> Text settings_enabledReleaseStages :: Settings -> [Text] settings_beforeNotify :: Settings -> BeforeNotify settings_ignoreException :: Settings -> Exception -> Bool settings_onNotifyException :: Settings -> HttpException -> IO () settings_codeIndex :: Settings -> Maybe CodeIndex settings_apiKey :: ApiKey settings_appVersion :: Maybe Text settings_releaseStage :: Text settings_enabledReleaseStages :: [Text] settings_beforeNotify :: BeforeNotify settings_ignoreException :: Exception -> Bool settings_onNotifyException :: HttpException -> IO () settings_codeIndex :: Maybe CodeIndex ..} = (Exception -> Bool) -> BeforeNotify filterExceptions (Bool -> Bool not (Bool -> Bool) -> (Exception -> Bool) -> Exception -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . Exception -> Bool ignoreException) BeforeNotify -> BeforeNotify -> BeforeNotify forall a. Semigroup a => a -> a -> a <> BeforeNotify settings_beforeNotify BeforeNotify -> BeforeNotify -> BeforeNotify forall a. Semigroup a => a -> a -> a <> BeforeNotify -> (CodeIndex -> BeforeNotify) -> Maybe CodeIndex -> BeforeNotify forall b a. b -> (a -> b) -> Maybe a -> b maybe BeforeNotify forall a. Monoid a => a mempty CodeIndex -> BeforeNotify setStackFramesCode Maybe CodeIndex settings_codeIndex BeforeNotify -> BeforeNotify -> BeforeNotify forall a. Semigroup a => a -> a -> a <> (Event -> Event) -> BeforeNotify updateEvent Event -> Event setApp where ignoreException :: Exception -> Bool ignoreException Exception e | Text settings_releaseStage Text -> [Text] -> Bool forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool `notElem` [Text] settings_enabledReleaseStages = Bool True | Bool otherwise = Exception -> Bool settings_ignoreException Exception e setApp :: Event -> Event setApp Event event = Event event { event_app = Just $ defaultApp { app_version = settings_appVersion , app_releaseStage = Just settings_releaseStage } }