module Honeycomb.Config where
import Honeycomb.Types
import Data.Text (Text)
import Lens.Micro (Lens', lens)
import Data.ByteString (ByteString)
import Data.Word (Word64)
data Config = Config
{ Config -> Text
teamWritekey :: Text
, Config -> DatasetName
defaultDataset :: DatasetName
, Config -> Text
apiHost :: Text
, Config -> Maybe Word64
sampleRate :: Maybe Word64
, Config -> Word64
pendingQueueSize :: Word64
, Config -> Word64
sendThreads :: Word64
, Config -> Bool
sendBlocking :: Bool
, Config -> Bool
nullTransmission :: Bool
, Config -> ByteString
customUserAgent :: ByteString
}
class HasConfig a where
configL :: Lens' a Config
instance HasConfig Config where
configL :: Lens' Config Config
configL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall a. a -> a
id (\Config
_ Config
new -> Config
new)
config :: Text -> DatasetName -> Config
config :: Text -> DatasetName -> Config
config Text
k DatasetName
ds = Text
-> DatasetName
-> Text
-> Maybe Word64
-> Word64
-> Word64
-> Bool
-> Bool
-> ByteString
-> Config
Config Text
k DatasetName
ds Text
"api.honeycomb.io" forall a. Maybe a
Nothing Word64
1024 Word64
1 Bool
False Bool
False ByteString
""