bloodhound-0.20.0.2: Elasticsearch client library for Haskell
Safe HaskellNone
LanguageHaskell2010

Database.Bloodhound.Internal.Analysis

Synopsis

Documentation

data Analysis Source #

Instances

Instances details
Eq Analysis Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show Analysis Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic Analysis Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep Analysis :: Type -> Type #

Methods

from :: Analysis -> Rep Analysis x #

to :: Rep Analysis x -> Analysis #

ToJSON Analysis Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

FromJSON Analysis Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep Analysis Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep Analysis = D1 ('MetaData "Analysis" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (C1 ('MetaCons "Analysis" 'PrefixI 'True) ((S1 ('MetaSel ('Just "analysisAnalyzer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text AnalyzerDefinition)) :*: S1 ('MetaSel ('Just "analysisTokenizer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text TokenizerDefinition))) :*: (S1 ('MetaSel ('Just "analysisTokenFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text TokenFilterDefinition)) :*: S1 ('MetaSel ('Just "analysisCharFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text CharFilterDefinition)))))

newtype Tokenizer Source #

Constructors

Tokenizer Text 

Instances

Instances details
Eq Tokenizer Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show Tokenizer Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic Tokenizer Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep Tokenizer :: Type -> Type #

ToJSON Tokenizer Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

FromJSON Tokenizer Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep Tokenizer Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep Tokenizer = D1 ('MetaData "Tokenizer" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'True) (C1 ('MetaCons "Tokenizer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data AnalyzerDefinition Source #

Instances

Instances details
Eq AnalyzerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show AnalyzerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic AnalyzerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep AnalyzerDefinition :: Type -> Type #

ToJSON AnalyzerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

FromJSON AnalyzerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep AnalyzerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep AnalyzerDefinition = D1 ('MetaData "AnalyzerDefinition" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (C1 ('MetaCons "AnalyzerDefinition" 'PrefixI 'True) (S1 ('MetaSel ('Just "analyzerDefinitionTokenizer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Tokenizer)) :*: (S1 ('MetaSel ('Just "analyzerDefinitionFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TokenFilter]) :*: S1 ('MetaSel ('Just "analyzerDefinitionCharFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CharFilter]))))

data TokenizerDefinition Source #

Instances

Instances details
Eq TokenizerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show TokenizerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic TokenizerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep TokenizerDefinition :: Type -> Type #

ToJSON TokenizerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

FromJSON TokenizerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep TokenizerDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep TokenizerDefinition = D1 ('MetaData "TokenizerDefinition" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (C1 ('MetaCons "TokenizerDefinitionNgram" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ngram)) :+: C1 ('MetaCons "TokenizerDefinitionEdgeNgram" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ngram)))

data Ngram Source #

Constructors

Ngram 

Instances

Instances details
Eq Ngram Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Methods

(==) :: Ngram -> Ngram -> Bool #

(/=) :: Ngram -> Ngram -> Bool #

Show Ngram Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Methods

showsPrec :: Int -> Ngram -> ShowS #

show :: Ngram -> String #

showList :: [Ngram] -> ShowS #

Generic Ngram Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep Ngram :: Type -> Type #

Methods

from :: Ngram -> Rep Ngram x #

to :: Rep Ngram x -> Ngram #

type Rep Ngram Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep Ngram = D1 ('MetaData "Ngram" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (C1 ('MetaCons "Ngram" 'PrefixI 'True) (S1 ('MetaSel ('Just "ngramMinGram") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "ngramMaxGram") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "ngramTokenChars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TokenChar]))))

data TokenChar Source #

Instances

Instances details
Eq TokenChar Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show TokenChar Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic TokenChar Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep TokenChar :: Type -> Type #

ToJSON TokenChar Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

FromJSON TokenChar Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep TokenChar Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep TokenChar = D1 ('MetaData "TokenChar" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) ((C1 ('MetaCons "TokenLetter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TokenDigit" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TokenWhitespace" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TokenPunctuation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TokenSymbol" 'PrefixI 'False) (U1 :: Type -> Type))))

data TokenFilterDefinition Source #

Token filters are used to create custom analyzers.

Instances

Instances details
Eq TokenFilterDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show TokenFilterDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic TokenFilterDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep TokenFilterDefinition :: Type -> Type #

ToJSON TokenFilterDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

FromJSON TokenFilterDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep TokenFilterDefinition Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep TokenFilterDefinition = D1 ('MetaData "TokenFilterDefinition" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (((C1 ('MetaCons "TokenFilterDefinitionLowercase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Language))) :+: C1 ('MetaCons "TokenFilterDefinitionUppercase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Language)))) :+: (C1 ('MetaCons "TokenFilterDefinitionApostrophe" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TokenFilterDefinitionReverse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TokenFilterDefinitionSnowball" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Language))))) :+: ((C1 ('MetaCons "TokenFilterDefinitionShingle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Shingle)) :+: (C1 ('MetaCons "TokenFilterDefinitionStemmer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Language)) :+: C1 ('MetaCons "TokenFilterDefinitionStop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either Language [StopWord]))))) :+: (C1 ('MetaCons "TokenFilterDefinitionEdgeNgram" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NgramFilter) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EdgeNgramFilterSide))) :+: (C1 ('MetaCons "TokenFilterDefinitionNgram" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NgramFilter)) :+: C1 ('MetaCons "TokenFilterTruncate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))))

data NgramFilter Source #

Instances

Instances details
Eq NgramFilter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show NgramFilter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic NgramFilter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep NgramFilter :: Type -> Type #

type Rep NgramFilter Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep NgramFilter = D1 ('MetaData "NgramFilter" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (C1 ('MetaCons "NgramFilter" 'PrefixI 'True) (S1 ('MetaSel ('Just "ngramFilterMinGram") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "ngramFilterMaxGram") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data EdgeNgramFilterSide Source #

Instances

Instances details
Eq EdgeNgramFilterSide Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show EdgeNgramFilterSide Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic EdgeNgramFilterSide Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep EdgeNgramFilterSide :: Type -> Type #

ToJSON EdgeNgramFilterSide Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

FromJSON EdgeNgramFilterSide Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep EdgeNgramFilterSide Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep EdgeNgramFilterSide = D1 ('MetaData "EdgeNgramFilterSide" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (C1 ('MetaCons "EdgeNgramFilterSideFront" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EdgeNgramFilterSideBack" 'PrefixI 'False) (U1 :: Type -> Type))

data Language Source #

The set of languages that can be passed to various analyzers, filters, etc. in Elasticsearch. Most data types in this module that have a Language field are actually only actually to handle a subset of these languages. Consult the official Elasticsearch documentation to see what is actually supported.

Instances

Instances details
Eq Language Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Show Language Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic Language Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep Language :: Type -> Type #

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

ToJSON Language Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

FromJSON Language Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep Language Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep Language = D1 ('MetaData "Language" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (((((C1 ('MetaCons "Arabic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Armenian" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Basque" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bengali" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Brazilian" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bulgarian" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Catalan" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Cjk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Czech" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Danish" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Dutch" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "English" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Finnish" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "French" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Galician" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "German" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "German2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Greek" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Hindi" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Hungarian" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Indonesian" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Irish" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Italian" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Kp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Latvian" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Lithuanian" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Lovins" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Norwegian" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Persian" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Porter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Portuguese" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Romanian" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Russian" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Sorani" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Spanish" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Swedish" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Thai" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Turkish" 'PrefixI 'False) (U1 :: Type -> Type)))))))

data Shingle Source #

Instances

Instances details
Eq Shingle Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Methods

(==) :: Shingle -> Shingle -> Bool #

(/=) :: Shingle -> Shingle -> Bool #

Show Shingle Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Generic Shingle Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

Associated Types

type Rep Shingle :: Type -> Type #

Methods

from :: Shingle -> Rep Shingle x #

to :: Rep Shingle x -> Shingle #

type Rep Shingle Source # 
Instance details

Defined in Database.Bloodhound.Internal.Analysis

type Rep Shingle = D1 ('MetaData "Shingle" "Database.Bloodhound.Internal.Analysis" "bloodhound-0.20.0.2-9g12ggjhChv8jJT8C6bH2X" 'False) (C1 ('MetaCons "Shingle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "shingleMaxSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "shingleMinSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "shingleOutputUnigrams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "shingleOutputUnigramsIfNoShingles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "shingleTokenSeparator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "shingleFillerToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))