Safe Haskell | None |
---|---|
Language | Haskell2010 |
Includes a scribe that can be used to log structured, JSON log messages to ElasticSearch. These logs can be explored easily using kibana or your tool of choice. Supports ElasticSearch servers with version 1.x or 5.x by way of different configs.
Example of configuring for ES5:
import Control.Exception import Database.V5.Bloodhound import Network.HTTP.Client import Katip import Katip.Scribes.ElasticSearch main :: IO () main = do mgr <- newManager defaultManagerSettings let bhe = mkBHEnv (Server "http://localhost:9200") mgr esScribe <- mkEsScribe -- Reasonable for production defaultEsScribeCfgV5 -- Reasonable for single-node in development -- defaultEsScribeCfgV5 { essIndexSettings = IndexSettings (ShardCound 1) (ReplicaCount 0)} bhe (IndexName "all-indices-prefixed-with") (MappingName "application-logs") DebugS V3 let mkLogEnv = registerScribe "es" esScribe defaultScribeSettings =<< initLogEnv "MyApp" "production" bracket mkLogEnv closeScribes $ \le -> runKatipT le $ do logMsg "ns" InfoS "This goes to elasticsearch"
Important Note on Index Settings
defaultEsScribeCfg
inherits a set of default index settings from
the bloodhound
package. These settings at this time of writing
set the indices up to have 3 shards and 2 replicas. This is an
arguably reasonable default setting for production but may cause
problems for development. In development, your cluster may be
configured to seek a write quorum greater than 1. If you're running
ElasticSearch on a single node, this could cause your writes to
wait for a bit and then fail due to a lack of quorum. For development, we recommend setting your replica count to 0 or modifying your write quorum settings. For production, we recommend reading the
ElasticSearch Scaling Guide and choosing the appropriate settings,
keeping in mind that you can chage replica counts on a live index
but that changing shard counts requires recreating the index.
Synopsis
- mkEsScribe :: forall v. (ESVersion v, MonadIO (BH v IO)) => EsScribeCfg v -> BHEnv v -> IndexName v -> MappingName v -> Severity -> Verbosity -> IO Scribe
- data EsScribeSetupError
- data EsQueueSize
- mkEsQueueSize :: Int -> Maybe EsQueueSize
- data EsPoolSize
- mkEsPoolSize :: Int -> Maybe EsPoolSize
- data IndexShardingPolicy
- newtype IndexNameSegment = IndexNameSegment {}
- data EsScribeCfg v
- essRetryPolicy :: EsScribeCfg v -> RetryPolicy
- essQueueSize :: EsScribeCfg v -> EsQueueSize
- essPoolSize :: EsScribeCfg v -> EsPoolSize
- essAnnotateTypes :: EsScribeCfg v -> Bool
- essIndexSettings :: EsScribeCfg v -> IndexSettings v
- essIndexSharding :: EsScribeCfg v -> IndexShardingPolicy
- defaultEsScribeCfg :: EsScribeCfg ESV1
- defaultEsScribeCfgV1 :: EsScribeCfg ESV1
- defaultEsScribeCfgV5 :: EsScribeCfg ESV5
- defaultEsScribeCfg' :: ESVersion v => proxy v -> EsScribeCfg v
- data ESV1
- data ESV5
- mkDocId :: ESVersion v => proxy v -> IO (DocId v)
- module Katip.Scribes.ElasticSearch.Annotations
Building a scribe
:: (ESVersion v, MonadIO (BH v IO)) | |
=> EsScribeCfg v | |
-> BHEnv v | |
-> IndexName v | Treated as a prefix if index sharding is enabled |
-> MappingName v | |
-> Severity | |
-> Verbosity | |
-> IO Scribe |
The Any field tagged with a v
corresponds to the type of the
same name in the corresponding bloodhound
module. For instance,
if you are configuring for ElasticSearch version 1, import
Database.V1.Bloodhound
and BHEnv v
will refer to BHEnv
from
that module, IndexName v
will repsond to IndexName
from that
module, etc.
Scribe configuration
data EsScribeSetupError Source #
CouldNotCreateIndex !(Response ByteString) | |
CouldNotUpdateIndexSettings !(Response ByteString) | |
CouldNotCreateMapping !(Response ByteString) | |
CouldNotPutTemplate !(Response ByteString) |
Instances
Show EsScribeSetupError Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal showsPrec :: Int -> EsScribeSetupError -> ShowS # show :: EsScribeSetupError -> String # showList :: [EsScribeSetupError] -> ShowS # | |
Exception EsScribeSetupError Source # | |
data EsQueueSize Source #
Instances
Bounded EsQueueSize Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal minBound :: EsQueueSize # maxBound :: EsQueueSize # | |
Eq EsQueueSize Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal (==) :: EsQueueSize -> EsQueueSize -> Bool # (/=) :: EsQueueSize -> EsQueueSize -> Bool # | |
Ord EsQueueSize Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal compare :: EsQueueSize -> EsQueueSize -> Ordering # (<) :: EsQueueSize -> EsQueueSize -> Bool # (<=) :: EsQueueSize -> EsQueueSize -> Bool # (>) :: EsQueueSize -> EsQueueSize -> Bool # (>=) :: EsQueueSize -> EsQueueSize -> Bool # max :: EsQueueSize -> EsQueueSize -> EsQueueSize # min :: EsQueueSize -> EsQueueSize -> EsQueueSize # | |
Show EsQueueSize Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal showsPrec :: Int -> EsQueueSize -> ShowS # show :: EsQueueSize -> String # showList :: [EsQueueSize] -> ShowS # |
mkEsQueueSize :: Int -> Maybe EsQueueSize Source #
data EsPoolSize Source #
Instances
Bounded EsPoolSize Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal minBound :: EsPoolSize # maxBound :: EsPoolSize # | |
Eq EsPoolSize Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal (==) :: EsPoolSize -> EsPoolSize -> Bool # (/=) :: EsPoolSize -> EsPoolSize -> Bool # | |
Ord EsPoolSize Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal compare :: EsPoolSize -> EsPoolSize -> Ordering # (<) :: EsPoolSize -> EsPoolSize -> Bool # (<=) :: EsPoolSize -> EsPoolSize -> Bool # (>) :: EsPoolSize -> EsPoolSize -> Bool # (>=) :: EsPoolSize -> EsPoolSize -> Bool # max :: EsPoolSize -> EsPoolSize -> EsPoolSize # min :: EsPoolSize -> EsPoolSize -> EsPoolSize # | |
Show EsPoolSize Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal showsPrec :: Int -> EsPoolSize -> ShowS # show :: EsPoolSize -> String # showList :: [EsPoolSize] -> ShowS # |
mkEsPoolSize :: Int -> Maybe EsPoolSize Source #
data IndexShardingPolicy Source #
How should katip store your log data?
- NoIndexSharding will store all logs in one index name. This is the simplest option but is not advised in production. In practice, the index will grow very large and will get slower to search. Deleting records based on some sort of retention period is also extremely slow.
- MonthlyIndexSharding, DailyIndexSharding, HourlyIndexSharding,
EveryMinuteIndexSharding will generate indexes based on the time of
the log. Index name is treated as a prefix. So if your index name
is
foo
and DailySharding is used, logs will be stored infoo-2016-2-25
,foo-2016-2-26
and so on. Index templating will be used to set up mappings automatically. Deletes based on date are very fast and queries can be restricted to date ranges for better performance. Queries against all dates should usefoo-*
as an index name. Note that index aliasing's glob feature is not suitable for these date ranges as it matches index names as they are declared, so new dates will be excluded. DailyIndexSharding is a reasonable choice. Changing index sharding strategies is not advisable. - CustomSharding: supply your own function that decomposes an item
into its index name hierarchy which will be appended to the index
name. So for instance if your function return ["arbitrary",
"prefix"], the index will be
foo-arbitrary-prefix
and the index template will be set to matchfoo-*
. In general, you want to use segments of increasing granularity (like year, month, day for dates). This makes it easier to address groups of indexes (e.g.foo-2016-*
).
NoIndexSharding | |
MonthlyIndexSharding | |
WeeklyIndexSharding | A special case of daily which shards to sunday |
DailyIndexSharding | |
HourlyIndexSharding | |
EveryMinuteIndexSharding | |
CustomIndexSharding (forall a. Item a -> [IndexNameSegment]) |
Instances
Show IndexShardingPolicy Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal showsPrec :: Int -> IndexShardingPolicy -> ShowS # show :: IndexShardingPolicy -> String # showList :: [IndexShardingPolicy] -> ShowS # |
newtype IndexNameSegment Source #
Instances
Eq IndexNameSegment Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal (==) :: IndexNameSegment -> IndexNameSegment -> Bool # (/=) :: IndexNameSegment -> IndexNameSegment -> Bool # | |
Ord IndexNameSegment Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal compare :: IndexNameSegment -> IndexNameSegment -> Ordering # (<) :: IndexNameSegment -> IndexNameSegment -> Bool # (<=) :: IndexNameSegment -> IndexNameSegment -> Bool # (>) :: IndexNameSegment -> IndexNameSegment -> Bool # (>=) :: IndexNameSegment -> IndexNameSegment -> Bool # max :: IndexNameSegment -> IndexNameSegment -> IndexNameSegment # min :: IndexNameSegment -> IndexNameSegment -> IndexNameSegment # | |
Show IndexNameSegment Source # | |
Defined in Katip.Scribes.ElasticSearch.Internal showsPrec :: Int -> IndexNameSegment -> ShowS # show :: IndexNameSegment -> String # showList :: [IndexNameSegment] -> ShowS # |
EsScribeCfg and fields
data EsScribeCfg v Source #
EsScribeCfg now carries a type variable for the version of
ElasticSearch it targets, either ESV1
or ESV5
. You can use
defaultEsScribeCfgV1
and defaultESScribeCfgV5
for a good
starting point depending on the ES version you have.
essRetryPolicy :: EsScribeCfg v -> RetryPolicy Source #
Retry policy when there are errors sending logs to the server
essQueueSize :: EsScribeCfg v -> EsQueueSize Source #
Maximum size of the bounded log queue
essPoolSize :: EsScribeCfg v -> EsPoolSize Source #
Worker pool size limit for sending data to the
essAnnotateTypes :: EsScribeCfg v -> Bool Source #
Different payload items coexist in the "data" attribute in ES. It is possible for different payloads to have different types for the same key, e.g. an "id" key that is sometimes a number and sometimes a string. If you're having ES do dynamic mapping, the first log item will set the type and any that don't conform will be *discarded*. If you set this to True, keys will recursively be appended with their ES core type. e.g. "id" would become "id::l" and "id::s" automatically, so they won't conflict. When this library exposes a querying API, we will try to make deserialization and querying transparently remove the type annotations if this is enabled.
essIndexSettings :: EsScribeCfg v -> IndexSettings v Source #
This will be the IndexSettings type from the appropriate
bloodhound module, either Database.V1.Bloodhound
or
Database.V5.Bloodhound
defaultEsScribeCfg :: EsScribeCfg ESV1 Source #
Alias of defaultEsScribeCfgV1
to minimize API
breakage. Previous versions of katip-elasticsearch only supported
ES version 1.
defaultEsScribeCfgV1 :: EsScribeCfg ESV1 Source #
EsScribeCfg that will use ElasticSearch V1
defaultEsScribeCfgV5 :: EsScribeCfg ESV5 Source #
EsScribeCfg that will use ElasticSearch V5
Version-Proxied APIS
You may need these these functions and types if type inference
fails. For instance, you may need to hint to the compiler that a
config is :: EsScribeCfg ESV5
, for instance.
defaultEsScribeCfg' :: ESVersion v => proxy v -> EsScribeCfg v Source #
Reasonable defaults for a config:
- defaultManagerSettings
- exponential backoff with 25ms base delay up to 5 retries
- Queue size of 1000
- Pool size of 2
- Annotate types set to False
- DailyIndexSharding