{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Database.Bloodhound.Internal.Highlight where
import Bloodhound.Import
import qualified Data.Map.Strict as M
import Database.Bloodhound.Internal.Newtypes
import Database.Bloodhound.Internal.Query
type HitHighlight = M.Map Text [Text]
data Highlights = Highlights
{ Highlights -> Maybe HighlightSettings
globalsettings :: Maybe HighlightSettings
, Highlights -> [FieldHighlight]
highlightFields :: [FieldHighlight]
} deriving (Highlights -> Highlights -> Bool
(Highlights -> Highlights -> Bool)
-> (Highlights -> Highlights -> Bool) -> Eq Highlights
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Highlights -> Highlights -> Bool
$c/= :: Highlights -> Highlights -> Bool
== :: Highlights -> Highlights -> Bool
$c== :: Highlights -> Highlights -> Bool
Eq, Int -> Highlights -> ShowS
[Highlights] -> ShowS
Highlights -> String
(Int -> Highlights -> ShowS)
-> (Highlights -> String)
-> ([Highlights] -> ShowS)
-> Show Highlights
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Highlights] -> ShowS
$cshowList :: [Highlights] -> ShowS
show :: Highlights -> String
$cshow :: Highlights -> String
showsPrec :: Int -> Highlights -> ShowS
$cshowsPrec :: Int -> Highlights -> ShowS
Show)
instance ToJSON Highlights where
toJSON :: Highlights -> Value
toJSON (Highlights Maybe HighlightSettings
global [FieldHighlight]
fields) =
[(Key, Value)] -> Value
omitNulls ((Key
"fields" Key -> [FieldHighlight] -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [FieldHighlight]
fields)
(Key, Value) -> [(Key, Value)] -> [(Key, Value)]
forall a. a -> [a] -> [a]
: Maybe HighlightSettings -> [(Key, Value)]
highlightSettingsPairs Maybe HighlightSettings
global)
data FieldHighlight =
FieldHighlight FieldName (Maybe HighlightSettings)
deriving (FieldHighlight -> FieldHighlight -> Bool
(FieldHighlight -> FieldHighlight -> Bool)
-> (FieldHighlight -> FieldHighlight -> Bool) -> Eq FieldHighlight
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldHighlight -> FieldHighlight -> Bool
$c/= :: FieldHighlight -> FieldHighlight -> Bool
== :: FieldHighlight -> FieldHighlight -> Bool
$c== :: FieldHighlight -> FieldHighlight -> Bool
Eq, Int -> FieldHighlight -> ShowS
[FieldHighlight] -> ShowS
FieldHighlight -> String
(Int -> FieldHighlight -> ShowS)
-> (FieldHighlight -> String)
-> ([FieldHighlight] -> ShowS)
-> Show FieldHighlight
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldHighlight] -> ShowS
$cshowList :: [FieldHighlight] -> ShowS
show :: FieldHighlight -> String
$cshow :: FieldHighlight -> String
showsPrec :: Int -> FieldHighlight -> ShowS
$cshowsPrec :: Int -> FieldHighlight -> ShowS
Show)
instance ToJSON FieldHighlight where
toJSON :: FieldHighlight -> Value
toJSON (FieldHighlight (FieldName Text
fName) (Just HighlightSettings
fSettings)) =
[(Key, Value)] -> Value
object [ Text -> Key
fromText Text
fName Key -> HighlightSettings -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HighlightSettings
fSettings ]
toJSON (FieldHighlight (FieldName Text
fName) Maybe HighlightSettings
Nothing) =
[(Key, Value)] -> Value
object [ Text -> Key
fromText Text
fName Key -> Value -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value
emptyObject ]
data HighlightSettings =
Plain PlainHighlight
| Postings PostingsHighlight
| FastVector FastVectorHighlight
deriving (HighlightSettings -> HighlightSettings -> Bool
(HighlightSettings -> HighlightSettings -> Bool)
-> (HighlightSettings -> HighlightSettings -> Bool)
-> Eq HighlightSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HighlightSettings -> HighlightSettings -> Bool
$c/= :: HighlightSettings -> HighlightSettings -> Bool
== :: HighlightSettings -> HighlightSettings -> Bool
$c== :: HighlightSettings -> HighlightSettings -> Bool
Eq, Int -> HighlightSettings -> ShowS
[HighlightSettings] -> ShowS
HighlightSettings -> String
(Int -> HighlightSettings -> ShowS)
-> (HighlightSettings -> String)
-> ([HighlightSettings] -> ShowS)
-> Show HighlightSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HighlightSettings] -> ShowS
$cshowList :: [HighlightSettings] -> ShowS
show :: HighlightSettings -> String
$cshow :: HighlightSettings -> String
showsPrec :: Int -> HighlightSettings -> ShowS
$cshowsPrec :: Int -> HighlightSettings -> ShowS
Show)
instance ToJSON HighlightSettings where
toJSON :: HighlightSettings -> Value
toJSON HighlightSettings
hs = [(Key, Value)] -> Value
omitNulls (Maybe HighlightSettings -> [(Key, Value)]
highlightSettingsPairs (HighlightSettings -> Maybe HighlightSettings
forall a. a -> Maybe a
Just HighlightSettings
hs))
data PlainHighlight =
PlainHighlight { PlainHighlight -> Maybe CommonHighlight
plainCommon :: Maybe CommonHighlight
, PlainHighlight -> Maybe NonPostings
plainNonPost :: Maybe NonPostings }
deriving (PlainHighlight -> PlainHighlight -> Bool
(PlainHighlight -> PlainHighlight -> Bool)
-> (PlainHighlight -> PlainHighlight -> Bool) -> Eq PlainHighlight
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlainHighlight -> PlainHighlight -> Bool
$c/= :: PlainHighlight -> PlainHighlight -> Bool
== :: PlainHighlight -> PlainHighlight -> Bool
$c== :: PlainHighlight -> PlainHighlight -> Bool
Eq, Int -> PlainHighlight -> ShowS
[PlainHighlight] -> ShowS
PlainHighlight -> String
(Int -> PlainHighlight -> ShowS)
-> (PlainHighlight -> String)
-> ([PlainHighlight] -> ShowS)
-> Show PlainHighlight
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlainHighlight] -> ShowS
$cshowList :: [PlainHighlight] -> ShowS
show :: PlainHighlight -> String
$cshow :: PlainHighlight -> String
showsPrec :: Int -> PlainHighlight -> ShowS
$cshowsPrec :: Int -> PlainHighlight -> ShowS
Show)
data PostingsHighlight =
PostingsHighlight (Maybe CommonHighlight)
deriving (PostingsHighlight -> PostingsHighlight -> Bool
(PostingsHighlight -> PostingsHighlight -> Bool)
-> (PostingsHighlight -> PostingsHighlight -> Bool)
-> Eq PostingsHighlight
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostingsHighlight -> PostingsHighlight -> Bool
$c/= :: PostingsHighlight -> PostingsHighlight -> Bool
== :: PostingsHighlight -> PostingsHighlight -> Bool
$c== :: PostingsHighlight -> PostingsHighlight -> Bool
Eq, Int -> PostingsHighlight -> ShowS
[PostingsHighlight] -> ShowS
PostingsHighlight -> String
(Int -> PostingsHighlight -> ShowS)
-> (PostingsHighlight -> String)
-> ([PostingsHighlight] -> ShowS)
-> Show PostingsHighlight
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostingsHighlight] -> ShowS
$cshowList :: [PostingsHighlight] -> ShowS
show :: PostingsHighlight -> String
$cshow :: PostingsHighlight -> String
showsPrec :: Int -> PostingsHighlight -> ShowS
$cshowsPrec :: Int -> PostingsHighlight -> ShowS
Show)
data FastVectorHighlight = FastVectorHighlight
{ FastVectorHighlight -> Maybe CommonHighlight
fvCommon :: Maybe CommonHighlight
, FastVectorHighlight -> Maybe NonPostings
fvNonPostSettings :: Maybe NonPostings
, FastVectorHighlight -> Maybe Text
boundaryChars :: Maybe Text
, FastVectorHighlight -> Maybe Int
boundaryMaxScan :: Maybe Int
, FastVectorHighlight -> Maybe Int
fragmentOffset :: Maybe Int
, FastVectorHighlight -> [Text]
matchedFields :: [Text]
, FastVectorHighlight -> Maybe Int
phraseLimit :: Maybe Int
} deriving (FastVectorHighlight -> FastVectorHighlight -> Bool
(FastVectorHighlight -> FastVectorHighlight -> Bool)
-> (FastVectorHighlight -> FastVectorHighlight -> Bool)
-> Eq FastVectorHighlight
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FastVectorHighlight -> FastVectorHighlight -> Bool
$c/= :: FastVectorHighlight -> FastVectorHighlight -> Bool
== :: FastVectorHighlight -> FastVectorHighlight -> Bool
$c== :: FastVectorHighlight -> FastVectorHighlight -> Bool
Eq, Int -> FastVectorHighlight -> ShowS
[FastVectorHighlight] -> ShowS
FastVectorHighlight -> String
(Int -> FastVectorHighlight -> ShowS)
-> (FastVectorHighlight -> String)
-> ([FastVectorHighlight] -> ShowS)
-> Show FastVectorHighlight
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FastVectorHighlight] -> ShowS
$cshowList :: [FastVectorHighlight] -> ShowS
show :: FastVectorHighlight -> String
$cshow :: FastVectorHighlight -> String
showsPrec :: Int -> FastVectorHighlight -> ShowS
$cshowsPrec :: Int -> FastVectorHighlight -> ShowS
Show)
data CommonHighlight = CommonHighlight
{ CommonHighlight -> Maybe Text
order :: Maybe Text
, CommonHighlight -> Maybe Bool
forceSource :: Maybe Bool
, CommonHighlight -> Maybe HighlightTag
tag :: Maybe HighlightTag
, CommonHighlight -> Maybe HighlightEncoder
encoder :: Maybe HighlightEncoder
, CommonHighlight -> Maybe Int
noMatchSize :: Maybe Int
, CommonHighlight -> Maybe Query
highlightQuery :: Maybe Query
, CommonHighlight -> Maybe Bool
requireFieldMatch :: Maybe Bool
} deriving (CommonHighlight -> CommonHighlight -> Bool
(CommonHighlight -> CommonHighlight -> Bool)
-> (CommonHighlight -> CommonHighlight -> Bool)
-> Eq CommonHighlight
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommonHighlight -> CommonHighlight -> Bool
$c/= :: CommonHighlight -> CommonHighlight -> Bool
== :: CommonHighlight -> CommonHighlight -> Bool
$c== :: CommonHighlight -> CommonHighlight -> Bool
Eq, Int -> CommonHighlight -> ShowS
[CommonHighlight] -> ShowS
CommonHighlight -> String
(Int -> CommonHighlight -> ShowS)
-> (CommonHighlight -> String)
-> ([CommonHighlight] -> ShowS)
-> Show CommonHighlight
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommonHighlight] -> ShowS
$cshowList :: [CommonHighlight] -> ShowS
show :: CommonHighlight -> String
$cshow :: CommonHighlight -> String
showsPrec :: Int -> CommonHighlight -> ShowS
$cshowsPrec :: Int -> CommonHighlight -> ShowS
Show)
data NonPostings =
NonPostings { NonPostings -> Maybe Int
fragmentSize :: Maybe Int
, NonPostings -> Maybe Int
numberOfFragments :: Maybe Int
} deriving (NonPostings -> NonPostings -> Bool
(NonPostings -> NonPostings -> Bool)
-> (NonPostings -> NonPostings -> Bool) -> Eq NonPostings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonPostings -> NonPostings -> Bool
$c/= :: NonPostings -> NonPostings -> Bool
== :: NonPostings -> NonPostings -> Bool
$c== :: NonPostings -> NonPostings -> Bool
Eq, Int -> NonPostings -> ShowS
[NonPostings] -> ShowS
NonPostings -> String
(Int -> NonPostings -> ShowS)
-> (NonPostings -> String)
-> ([NonPostings] -> ShowS)
-> Show NonPostings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonPostings] -> ShowS
$cshowList :: [NonPostings] -> ShowS
show :: NonPostings -> String
$cshow :: NonPostings -> String
showsPrec :: Int -> NonPostings -> ShowS
$cshowsPrec :: Int -> NonPostings -> ShowS
Show)
data HighlightEncoder = DefaultEncoder
| HTMLEncoder
deriving (HighlightEncoder -> HighlightEncoder -> Bool
(HighlightEncoder -> HighlightEncoder -> Bool)
-> (HighlightEncoder -> HighlightEncoder -> Bool)
-> Eq HighlightEncoder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HighlightEncoder -> HighlightEncoder -> Bool
$c/= :: HighlightEncoder -> HighlightEncoder -> Bool
== :: HighlightEncoder -> HighlightEncoder -> Bool
$c== :: HighlightEncoder -> HighlightEncoder -> Bool
Eq, Int -> HighlightEncoder -> ShowS
[HighlightEncoder] -> ShowS
HighlightEncoder -> String
(Int -> HighlightEncoder -> ShowS)
-> (HighlightEncoder -> String)
-> ([HighlightEncoder] -> ShowS)
-> Show HighlightEncoder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HighlightEncoder] -> ShowS
$cshowList :: [HighlightEncoder] -> ShowS
show :: HighlightEncoder -> String
$cshow :: HighlightEncoder -> String
showsPrec :: Int -> HighlightEncoder -> ShowS
$cshowsPrec :: Int -> HighlightEncoder -> ShowS
Show)
instance ToJSON HighlightEncoder where
toJSON :: HighlightEncoder -> Value
toJSON HighlightEncoder
DefaultEncoder = Text -> Value
String Text
"default"
toJSON HighlightEncoder
HTMLEncoder = Text -> Value
String Text
"html"
data HighlightTag =
TagSchema Text
| CustomTags ([Text], [Text])
deriving (HighlightTag -> HighlightTag -> Bool
(HighlightTag -> HighlightTag -> Bool)
-> (HighlightTag -> HighlightTag -> Bool) -> Eq HighlightTag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HighlightTag -> HighlightTag -> Bool
$c/= :: HighlightTag -> HighlightTag -> Bool
== :: HighlightTag -> HighlightTag -> Bool
$c== :: HighlightTag -> HighlightTag -> Bool
Eq, Int -> HighlightTag -> ShowS
[HighlightTag] -> ShowS
HighlightTag -> String
(Int -> HighlightTag -> ShowS)
-> (HighlightTag -> String)
-> ([HighlightTag] -> ShowS)
-> Show HighlightTag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HighlightTag] -> ShowS
$cshowList :: [HighlightTag] -> ShowS
show :: HighlightTag -> String
$cshow :: HighlightTag -> String
showsPrec :: Int -> HighlightTag -> ShowS
$cshowsPrec :: Int -> HighlightTag -> ShowS
Show)
highlightSettingsPairs :: Maybe HighlightSettings -> [Pair]
highlightSettingsPairs :: Maybe HighlightSettings -> [(Key, Value)]
highlightSettingsPairs Maybe HighlightSettings
Nothing = []
highlightSettingsPairs (Just (Plain PlainHighlight
plh)) = Maybe PlainHighlight -> [(Key, Value)]
plainHighPairs (PlainHighlight -> Maybe PlainHighlight
forall a. a -> Maybe a
Just PlainHighlight
plh)
highlightSettingsPairs (Just (Postings PostingsHighlight
ph)) = Maybe PostingsHighlight -> [(Key, Value)]
postHighPairs (PostingsHighlight -> Maybe PostingsHighlight
forall a. a -> Maybe a
Just PostingsHighlight
ph)
highlightSettingsPairs (Just (FastVector FastVectorHighlight
fvh)) = Maybe FastVectorHighlight -> [(Key, Value)]
fastVectorHighPairs (FastVectorHighlight -> Maybe FastVectorHighlight
forall a. a -> Maybe a
Just FastVectorHighlight
fvh)
plainHighPairs :: Maybe PlainHighlight -> [Pair]
plainHighPairs :: Maybe PlainHighlight -> [(Key, Value)]
plainHighPairs Maybe PlainHighlight
Nothing = []
plainHighPairs (Just (PlainHighlight Maybe CommonHighlight
plCom Maybe NonPostings
plNonPost)) =
[ Key
"type" Key -> Value -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
"plain"]
[(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. [a] -> [a] -> [a]
++ Maybe CommonHighlight -> [(Key, Value)]
commonHighlightPairs Maybe CommonHighlight
plCom
[(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. [a] -> [a] -> [a]
++ Maybe NonPostings -> [(Key, Value)]
nonPostingsToPairs Maybe NonPostings
plNonPost
postHighPairs :: Maybe PostingsHighlight -> [Pair]
postHighPairs :: Maybe PostingsHighlight -> [(Key, Value)]
postHighPairs Maybe PostingsHighlight
Nothing = []
postHighPairs (Just (PostingsHighlight Maybe CommonHighlight
pCom)) =
(Key
"type" Key -> Value -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
"postings")
(Key, Value) -> [(Key, Value)] -> [(Key, Value)]
forall a. a -> [a] -> [a]
: Maybe CommonHighlight -> [(Key, Value)]
commonHighlightPairs Maybe CommonHighlight
pCom
fastVectorHighPairs :: Maybe FastVectorHighlight -> [Pair]
fastVectorHighPairs :: Maybe FastVectorHighlight -> [(Key, Value)]
fastVectorHighPairs Maybe FastVectorHighlight
Nothing = []
fastVectorHighPairs
(Just
(FastVectorHighlight Maybe CommonHighlight
fvCom Maybe NonPostings
fvNonPostSettings' Maybe Text
fvBoundChars
Maybe Int
fvBoundMaxScan Maybe Int
fvFragOff [Text]
fvMatchedFields
Maybe Int
fvPhraseLim)) =
[ Key
"type" Key -> Value -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
"fvh"
, Key
"boundary_chars" Key -> Maybe Text -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
fvBoundChars
, Key
"boundary_max_scan" Key -> Maybe Int -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
fvBoundMaxScan
, Key
"fragment_offset" Key -> Maybe Int -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
fvFragOff
, Key
"matched_fields" Key -> [Text] -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
fvMatchedFields
, Key
"phraseLimit" Key -> Maybe Int -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
fvPhraseLim]
[(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. [a] -> [a] -> [a]
++ Maybe CommonHighlight -> [(Key, Value)]
commonHighlightPairs Maybe CommonHighlight
fvCom
[(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. [a] -> [a] -> [a]
++ Maybe NonPostings -> [(Key, Value)]
nonPostingsToPairs Maybe NonPostings
fvNonPostSettings'
commonHighlightPairs :: Maybe CommonHighlight -> [Pair]
commonHighlightPairs :: Maybe CommonHighlight -> [(Key, Value)]
commonHighlightPairs Maybe CommonHighlight
Nothing = []
commonHighlightPairs (Just (CommonHighlight Maybe Text
chScore Maybe Bool
chForceSource
Maybe HighlightTag
chTag Maybe HighlightEncoder
chEncoder Maybe Int
chNoMatchSize
Maybe Query
chHighlightQuery Maybe Bool
chRequireFieldMatch)) =
[ Key
"order" Key -> Maybe Text -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
chScore
, Key
"force_source" Key -> Maybe Bool -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
chForceSource
, Key
"encoder" Key -> Maybe HighlightEncoder -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe HighlightEncoder
chEncoder
, Key
"no_match_size" Key -> Maybe Int -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
chNoMatchSize
, Key
"highlight_query" Key -> Maybe Query -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Query
chHighlightQuery
, Key
"require_fieldMatch" Key -> Maybe Bool -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
chRequireFieldMatch
]
[(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. [a] -> [a] -> [a]
++ Maybe HighlightTag -> [(Key, Value)]
highlightTagToPairs Maybe HighlightTag
chTag
nonPostingsToPairs :: Maybe NonPostings -> [Pair]
nonPostingsToPairs :: Maybe NonPostings -> [(Key, Value)]
nonPostingsToPairs Maybe NonPostings
Nothing = []
nonPostingsToPairs (Just (NonPostings Maybe Int
npFragSize Maybe Int
npNumOfFrags)) =
[ Key
"fragment_size" Key -> Maybe Int -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
npFragSize
, Key
"number_of_fragments" Key -> Maybe Int -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
npNumOfFrags
]
highlightTagToPairs :: Maybe HighlightTag -> [Pair]
highlightTagToPairs :: Maybe HighlightTag -> [(Key, Value)]
highlightTagToPairs (Just (TagSchema Text
_)) =
[ Key
"scheme" Key -> Value -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
"default"
]
highlightTagToPairs (Just (CustomTags ([Text]
pre, [Text]
post))) =
[ Key
"pre_tags" Key -> [Text] -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
pre
, Key
"post_tags" Key -> [Text] -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
post
]
highlightTagToPairs Maybe HighlightTag
Nothing = []