Safe Haskell | None |
---|---|
Language | Haskell2010 |
This is an internal module. No guarantees are made in this module about API stability.
Synopsis
- data EsScribeCfg v = EsScribeCfg {}
- defaultEsScribeCfg' :: ESVersion v => proxy v -> EsScribeCfg v
- defaultEsScribeCfg :: EsScribeCfg ESV1
- defaultEsScribeCfgV1 :: EsScribeCfg ESV1
- defaultEsScribeCfgV5 :: EsScribeCfg ESV5
- data IndexShardingPolicy
- newtype IndexNameSegment = IndexNameSegment {}
- shardPolicySegs :: IndexShardingPolicy -> Item a -> [IndexNameSegment]
- roundToSunday :: Day -> Day
- chooseIxn :: ESVersion v => proxy v -> IndexName v -> IndexShardingPolicy -> Item a -> IndexName v
- sis :: Integral a => a -> IndexNameSegment
- splitTime :: DiffTime -> (Int, Int)
- data EsScribeSetupError
- mkEsScribe :: forall v. (ESVersion v, MonadIO (BH v IO)) => EsScribeCfg v -> BHEnv v -> IndexName v -> MappingName v -> Severity -> Verbosity -> IO Scribe
- baseMapping :: ESVersion v => proxy v -> MappingName v -> Value
- esDateFormat :: Text
- mkDocId :: ESVersion v => proxy v -> IO (DocId v)
- newtype EsQueueSize = EsQueueSize {
- unEsQueueSize :: Int
- mkEsQueueSize :: Int -> Maybe EsQueueSize
- newtype EsPoolSize = EsPoolSize {
- unEsPoolSize :: Int
- mkEsPoolSize :: Int -> Maybe EsPoolSize
- mkNonZero :: (Int -> a) -> Int -> Maybe a
- startWorker :: forall v. ESVersion v => EsScribeCfg v -> BHEnv v -> MappingName v -> TBMQueue (IndexName v, Value) -> IO ()
- class ESVersion v where
- type BHEnv v
- type IndexSettings v
- type UpdatableIndexSetting v
- type IndexName v
- type MappingName v
- type DocId v
- type BH v :: (* -> *) -> * -> *
- type TemplateName v
- type TemplatePattern v
- type IndexTemplate v
- type IndexDocumentSettings v
- defaultIndexSettings :: proxy v -> IndexSettings v
- toIndexName :: proxy v -> Text -> IndexName v
- fromIndexName :: proxy v -> IndexName v -> Text
- fromMappingName :: proxy v -> MappingName v -> Text
- toDocId :: proxy v -> Text -> DocId v
- runBH :: proxy v -> BHEnv v -> BH v m a -> m a
- toTemplateName :: proxy v -> Text -> TemplateName v
- toTemplatePattern :: proxy v -> Text -> TemplatePattern v
- toIndexTemplate :: proxy v -> TemplatePattern v -> Maybe (IndexSettings v) -> [Value] -> IndexTemplate v
- defaultIndexDocumentSettings :: proxy v -> IndexDocumentSettings v
- toUpdatabaleIndexSettings :: proxy v -> IndexSettings v -> NonEmpty (UpdatableIndexSetting v)
- indexExists :: proxy v -> IndexName v -> BH v IO Bool
- indexDocument :: ToJSON doc => proxy v -> IndexName v -> MappingName v -> IndexDocumentSettings v -> doc -> DocId v -> BH v IO (Response ByteString)
- createIndex :: proxy v -> IndexSettings v -> IndexName v -> BH v IO (Response ByteString)
- updateIndexSettings :: proxy v -> NonEmpty (UpdatableIndexSetting v) -> IndexName v -> BH v IO (Response ByteString)
- putTemplate :: proxy v -> IndexTemplate v -> TemplateName v -> BH v IO (Response ByteString)
- putMapping :: ToJSON a => proxy v -> IndexName v -> MappingName v -> a -> BH v IO (Response ByteString)
- unanalyzedStringSpec :: proxy v -> Value
- analyzedStringSpec :: proxy v -> Value
- data ESV1 = ESV1
- data ESV5 = ESV5
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.
EsScribeCfg | |
|
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 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 # |
shardPolicySegs :: IndexShardingPolicy -> Item a -> [IndexNameSegment] Source #
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 #
sis :: Integral a => a -> IndexNameSegment Source #
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 # | |
:: (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.
baseMapping :: ESVersion v => proxy v -> MappingName v -> Value Source #
esDateFormat :: Text Source #
Handle both old-style aeson and picosecond-level precision
newtype 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 #
newtype 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 #
startWorker :: forall v. ESVersion v => EsScribeCfg v -> BHEnv v -> MappingName v -> TBMQueue (IndexName v, Value) -> IO () Source #
class ESVersion v where Source #
type IndexSettings v Source #
type UpdatableIndexSetting v Source #
type MappingName v Source #
type BH v :: (* -> *) -> * -> * Source #
type TemplateName v Source #
type TemplatePattern v Source #
type IndexTemplate v Source #
type IndexDocumentSettings v Source #
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 #
toUpdatabaleIndexSettings :: proxy v -> IndexSettings v -> NonEmpty (UpdatableIndexSetting 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 #
updateIndexSettings :: proxy v -> NonEmpty (UpdatableIndexSetting 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 #
unanalyzedStringSpec :: proxy v -> Value Source #
analyzedStringSpec :: proxy v -> Value Source #