module Data.Bugsnag.Settings
( Settings (..)
, defaultSettings
) where
import Prelude
import Data.Bugsnag
import Data.Text (Text)
import Network.Bugsnag.BeforeNotify
import Network.Bugsnag.CodeIndex
import Network.HTTP.Client (HttpException)
data Settings = Settings
{ Settings -> ApiKey
settings_apiKey :: ApiKey
, Settings -> Maybe Text
settings_appVersion :: Maybe Text
, Settings -> Text
settings_releaseStage :: Text
, Settings -> [Text]
settings_enabledReleaseStages :: [Text]
, Settings -> BeforeNotify
settings_beforeNotify :: BeforeNotify
, Settings -> Exception -> Bool
settings_ignoreException :: Exception -> Bool
, Settings -> HttpException -> IO ()
settings_onNotifyException :: HttpException -> IO ()
, Settings -> Maybe CodeIndex
settings_codeIndex :: Maybe CodeIndex
}
defaultSettings :: Text -> Settings
defaultSettings :: Text -> Settings
defaultSettings Text
k =
Settings
{ settings_apiKey :: ApiKey
settings_apiKey = Text -> ApiKey
apiKey Text
k
, settings_appVersion :: Maybe Text
settings_appVersion = Maybe Text
forall a. Maybe a
Nothing
, settings_releaseStage :: Text
settings_releaseStage = Text
"production"
, settings_enabledReleaseStages :: [Text]
settings_enabledReleaseStages = [Text
"production"]
, settings_beforeNotify :: BeforeNotify
settings_beforeNotify = BeforeNotify
forall a. Monoid a => a
mempty
, settings_ignoreException :: Exception -> Bool
settings_ignoreException = Bool -> Exception -> Bool
forall a b. a -> b -> a
const Bool
False
, settings_onNotifyException :: HttpException -> IO ()
settings_onNotifyException = IO () -> HttpException -> IO ()
forall a b. a -> b -> a
const (IO () -> HttpException -> IO ())
-> IO () -> HttpException -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
, settings_codeIndex :: Maybe CodeIndex
settings_codeIndex = Maybe CodeIndex
forall a. Maybe a
Nothing
}