katip-elasticsearch-0.4.0.0: ElasticSearch scribe for the Katip logging framework.

Safe HaskellNone
LanguageHaskell2010

Katip.Scribes.ElasticSearch.Internal

Description

This is an internal module. No guarantees are made in this module about API stability.

Synopsis

Documentation

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.

Constructors

EsScribeCfg 

Fields

essRetryPolicy :: RetryPolicy

Retry policy when there are errors sending logs to the server

essQueueSize :: EsQueueSize

Maximum size of the bounded log queue

essPoolSize :: EsPoolSize

Worker pool size limit for sending data to the

essAnnotateTypes :: Bool

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 :: IndexSettings v

This will be the IndexSettings type from the appropriate bloodhound module, either Database.V1.Bloodhound or Database.V5.Bloodhound

essIndexSharding :: IndexShardingPolicy
 

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

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

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 in foo-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 use foo-* 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 match foo-*. 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-*).

roundToSunday :: Day -> Day Source

If the given day is sunday, returns the input, otherwise returns the previous sunday

chooseIxn :: ESVersion v => proxy v -> IndexName v -> IndexShardingPolicy -> Item a -> IndexName v Source

mkEsScribe Source

Arguments

:: (ESVersion v, MonadIO (BH v IO), Functor (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.

baseMapping :: ESVersion v => proxy v -> MappingName v -> Value Source

esDateFormat :: Text Source

Handle both old-style aeson and picosecond-level precision

mkDocId :: ESVersion v => proxy v -> IO (DocId v) Source

mkNonZero :: (Int -> a) -> Int -> Maybe a Source

startWorker :: forall v. ESVersion v => EsScribeCfg v -> BHEnv v -> MappingName v -> TBMQueue (IndexName v, Value) -> IO () Source

class ESVersion v where Source

Associated Types

type BHEnv v Source

type IndexSettings v Source

type IndexName v Source

type MappingName v Source

type DocId v Source

type BH v :: (* -> *) -> * -> * Source

type TemplateName v Source

type TemplatePattern v Source

type IndexTemplate v Source

type IndexDocumentSettings v Source

Methods

defaultIndexSettings :: proxy v -> IndexSettings v Source

toIndexName :: proxy v -> Text -> IndexName v Source

fromIndexName :: proxy v -> IndexName v -> Text Source

fromMappingName :: proxy v -> MappingName v -> Text Source

toDocId :: proxy v -> Text -> DocId v Source

runBH :: proxy v -> BHEnv v -> BH v m a -> m a Source

toTemplateName :: proxy v -> Text -> TemplateName v Source

toTemplatePattern :: proxy v -> Text -> TemplatePattern v Source

toIndexTemplate :: proxy v -> TemplatePattern v -> Maybe (IndexSettings v) -> [Value] -> IndexTemplate v Source

defaultIndexDocumentSettings :: proxy v -> IndexDocumentSettings v Source

indexExists :: proxy v -> IndexName v -> BH v IO Bool Source

indexDocument :: ToJSON doc => proxy v -> IndexName v -> MappingName v -> IndexDocumentSettings v -> doc -> DocId v -> BH v IO (Response ByteString) Source

createIndex :: proxy v -> IndexSettings v -> IndexName v -> BH v IO (Response ByteString) Source

putTemplate :: proxy v -> IndexTemplate v -> TemplateName v -> BH v IO (Response ByteString) Source

putMapping :: ToJSON a => proxy v -> IndexName v -> MappingName v -> a -> BH v IO (Response ByteString) Source

data ESV1 Source

Constructors

ESV1 

Instances

ESVersion ESV1 Source 
type BHEnv ESV1 = BHEnv Source 
type IndexSettings ESV1 = IndexSettings Source 
type IndexName ESV1 = IndexName Source 
type MappingName ESV1 = MappingName Source 
type DocId ESV1 = DocId Source 
type BH ESV1 = BH Source 
type TemplateName ESV1 = TemplateName Source 
type TemplatePattern ESV1 = TemplatePattern Source 
type IndexTemplate ESV1 = IndexTemplate Source 
type IndexDocumentSettings ESV1 = IndexDocumentSettings Source 

data ESV5 Source

Constructors

ESV5 

Instances

ESVersion ESV5 Source 
type BHEnv ESV5 = BHEnv Source 
type IndexSettings ESV5 = IndexSettings Source 
type IndexName ESV5 = IndexName Source 
type MappingName ESV5 = MappingName Source 
type DocId ESV5 = DocId Source 
type BH ESV5 = BH Source 
type TemplateName ESV5 = TemplateName Source 
type TemplatePattern ESV5 = TemplatePattern Source 
type IndexTemplate ESV5 = IndexTemplate Source 
type IndexDocumentSettings ESV5 = IndexDocumentSettings Source