{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} module Database.Bloodhound.Common.Script where import Bloodhound.Import import Data.Aeson.KeyMap import Database.Bloodhound.Internal.Newtypes newtype ScriptFields = ScriptFields (KeyMap ScriptFieldValue) deriving (ScriptFields -> ScriptFields -> Bool (ScriptFields -> ScriptFields -> Bool) -> (ScriptFields -> ScriptFields -> Bool) -> Eq ScriptFields forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ScriptFields -> ScriptFields -> Bool $c/= :: ScriptFields -> ScriptFields -> Bool == :: ScriptFields -> ScriptFields -> Bool $c== :: ScriptFields -> ScriptFields -> Bool Eq, Int -> ScriptFields -> ShowS [ScriptFields] -> ShowS ScriptFields -> String (Int -> ScriptFields -> ShowS) -> (ScriptFields -> String) -> ([ScriptFields] -> ShowS) -> Show ScriptFields forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ScriptFields] -> ShowS $cshowList :: [ScriptFields] -> ShowS show :: ScriptFields -> String $cshow :: ScriptFields -> String showsPrec :: Int -> ScriptFields -> ShowS $cshowsPrec :: Int -> ScriptFields -> ShowS Show) type ScriptFieldValue = Value data ScriptSource = ScriptId Text | ScriptInline Text deriving (ScriptSource -> ScriptSource -> Bool (ScriptSource -> ScriptSource -> Bool) -> (ScriptSource -> ScriptSource -> Bool) -> Eq ScriptSource forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ScriptSource -> ScriptSource -> Bool $c/= :: ScriptSource -> ScriptSource -> Bool == :: ScriptSource -> ScriptSource -> Bool $c== :: ScriptSource -> ScriptSource -> Bool Eq, Int -> ScriptSource -> ShowS [ScriptSource] -> ShowS ScriptSource -> String (Int -> ScriptSource -> ShowS) -> (ScriptSource -> String) -> ([ScriptSource] -> ShowS) -> Show ScriptSource forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ScriptSource] -> ShowS $cshowList :: [ScriptSource] -> ShowS show :: ScriptSource -> String $cshow :: ScriptSource -> String showsPrec :: Int -> ScriptSource -> ShowS $cshowsPrec :: Int -> ScriptSource -> ShowS Show) data Script = Script { Script -> Maybe ScriptLanguage scriptLanguage :: Maybe ScriptLanguage , Script -> ScriptSource scriptSource :: ScriptSource , Script -> Maybe ScriptParams scriptParams :: Maybe ScriptParams } deriving (Script -> Script -> Bool (Script -> Script -> Bool) -> (Script -> Script -> Bool) -> Eq Script forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Script -> Script -> Bool $c/= :: Script -> Script -> Bool == :: Script -> Script -> Bool $c== :: Script -> Script -> Bool Eq, Int -> Script -> ShowS [Script] -> ShowS Script -> String (Int -> Script -> ShowS) -> (Script -> String) -> ([Script] -> ShowS) -> Show Script forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Script] -> ShowS $cshowList :: [Script] -> ShowS show :: Script -> String $cshow :: Script -> String showsPrec :: Int -> Script -> ShowS $cshowsPrec :: Int -> Script -> ShowS Show) newtype ScriptLanguage = ScriptLanguage Text deriving (ScriptLanguage -> ScriptLanguage -> Bool (ScriptLanguage -> ScriptLanguage -> Bool) -> (ScriptLanguage -> ScriptLanguage -> Bool) -> Eq ScriptLanguage forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ScriptLanguage -> ScriptLanguage -> Bool $c/= :: ScriptLanguage -> ScriptLanguage -> Bool == :: ScriptLanguage -> ScriptLanguage -> Bool $c== :: ScriptLanguage -> ScriptLanguage -> Bool Eq, Int -> ScriptLanguage -> ShowS [ScriptLanguage] -> ShowS ScriptLanguage -> String (Int -> ScriptLanguage -> ShowS) -> (ScriptLanguage -> String) -> ([ScriptLanguage] -> ShowS) -> Show ScriptLanguage forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ScriptLanguage] -> ShowS $cshowList :: [ScriptLanguage] -> ShowS show :: ScriptLanguage -> String $cshow :: ScriptLanguage -> String showsPrec :: Int -> ScriptLanguage -> ShowS $cshowsPrec :: Int -> ScriptLanguage -> ShowS Show, Value -> Parser [ScriptLanguage] Value -> Parser ScriptLanguage (Value -> Parser ScriptLanguage) -> (Value -> Parser [ScriptLanguage]) -> FromJSON ScriptLanguage forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [ScriptLanguage] $cparseJSONList :: Value -> Parser [ScriptLanguage] parseJSON :: Value -> Parser ScriptLanguage $cparseJSON :: Value -> Parser ScriptLanguage FromJSON, [ScriptLanguage] -> Encoding [ScriptLanguage] -> Value ScriptLanguage -> Encoding ScriptLanguage -> Value (ScriptLanguage -> Value) -> (ScriptLanguage -> Encoding) -> ([ScriptLanguage] -> Value) -> ([ScriptLanguage] -> Encoding) -> ToJSON ScriptLanguage forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [ScriptLanguage] -> Encoding $ctoEncodingList :: [ScriptLanguage] -> Encoding toJSONList :: [ScriptLanguage] -> Value $ctoJSONList :: [ScriptLanguage] -> Value toEncoding :: ScriptLanguage -> Encoding $ctoEncoding :: ScriptLanguage -> Encoding toJSON :: ScriptLanguage -> Value $ctoJSON :: ScriptLanguage -> Value ToJSON) newtype ScriptParams = ScriptParams (KeyMap ScriptParamValue) deriving (ScriptParams -> ScriptParams -> Bool (ScriptParams -> ScriptParams -> Bool) -> (ScriptParams -> ScriptParams -> Bool) -> Eq ScriptParams forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ScriptParams -> ScriptParams -> Bool $c/= :: ScriptParams -> ScriptParams -> Bool == :: ScriptParams -> ScriptParams -> Bool $c== :: ScriptParams -> ScriptParams -> Bool Eq, Int -> ScriptParams -> ShowS [ScriptParams] -> ShowS ScriptParams -> String (Int -> ScriptParams -> ShowS) -> (ScriptParams -> String) -> ([ScriptParams] -> ShowS) -> Show ScriptParams forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ScriptParams] -> ShowS $cshowList :: [ScriptParams] -> ShowS show :: ScriptParams -> String $cshow :: ScriptParams -> String showsPrec :: Int -> ScriptParams -> ShowS $cshowsPrec :: Int -> ScriptParams -> ShowS Show) type ScriptParamValue = Value data BoostMode = BoostModeMultiply | BoostModeReplace | BoostModeSum | BoostModeAvg | BoostModeMax | BoostModeMin deriving (BoostMode -> BoostMode -> Bool (BoostMode -> BoostMode -> Bool) -> (BoostMode -> BoostMode -> Bool) -> Eq BoostMode forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: BoostMode -> BoostMode -> Bool $c/= :: BoostMode -> BoostMode -> Bool == :: BoostMode -> BoostMode -> Bool $c== :: BoostMode -> BoostMode -> Bool Eq, Int -> BoostMode -> ShowS [BoostMode] -> ShowS BoostMode -> String (Int -> BoostMode -> ShowS) -> (BoostMode -> String) -> ([BoostMode] -> ShowS) -> Show BoostMode forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [BoostMode] -> ShowS $cshowList :: [BoostMode] -> ShowS show :: BoostMode -> String $cshow :: BoostMode -> String showsPrec :: Int -> BoostMode -> ShowS $cshowsPrec :: Int -> BoostMode -> ShowS Show) data ScoreMode = ScoreModeMultiply | ScoreModeSum | ScoreModeAvg | ScoreModeFirst | ScoreModeMax | ScoreModeMin deriving (ScoreMode -> ScoreMode -> Bool (ScoreMode -> ScoreMode -> Bool) -> (ScoreMode -> ScoreMode -> Bool) -> Eq ScoreMode forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ScoreMode -> ScoreMode -> Bool $c/= :: ScoreMode -> ScoreMode -> Bool == :: ScoreMode -> ScoreMode -> Bool $c== :: ScoreMode -> ScoreMode -> Bool Eq, Int -> ScoreMode -> ShowS [ScoreMode] -> ShowS ScoreMode -> String (Int -> ScoreMode -> ShowS) -> (ScoreMode -> String) -> ([ScoreMode] -> ShowS) -> Show ScoreMode forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ScoreMode] -> ShowS $cshowList :: [ScoreMode] -> ShowS show :: ScoreMode -> String $cshow :: ScoreMode -> String showsPrec :: Int -> ScoreMode -> ShowS $cshowsPrec :: Int -> ScoreMode -> ShowS Show) data FunctionScoreFunction = FunctionScoreFunctionScript Script | FunctionScoreFunctionRandom Seed | FunctionScoreFunctionFieldValueFactor FieldValueFactor deriving (FunctionScoreFunction -> FunctionScoreFunction -> Bool (FunctionScoreFunction -> FunctionScoreFunction -> Bool) -> (FunctionScoreFunction -> FunctionScoreFunction -> Bool) -> Eq FunctionScoreFunction forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: FunctionScoreFunction -> FunctionScoreFunction -> Bool $c/= :: FunctionScoreFunction -> FunctionScoreFunction -> Bool == :: FunctionScoreFunction -> FunctionScoreFunction -> Bool $c== :: FunctionScoreFunction -> FunctionScoreFunction -> Bool Eq, Int -> FunctionScoreFunction -> ShowS [FunctionScoreFunction] -> ShowS FunctionScoreFunction -> String (Int -> FunctionScoreFunction -> ShowS) -> (FunctionScoreFunction -> String) -> ([FunctionScoreFunction] -> ShowS) -> Show FunctionScoreFunction forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [FunctionScoreFunction] -> ShowS $cshowList :: [FunctionScoreFunction] -> ShowS show :: FunctionScoreFunction -> String $cshow :: FunctionScoreFunction -> String showsPrec :: Int -> FunctionScoreFunction -> ShowS $cshowsPrec :: Int -> FunctionScoreFunction -> ShowS Show) newtype Weight = Weight Float deriving (Weight -> Weight -> Bool (Weight -> Weight -> Bool) -> (Weight -> Weight -> Bool) -> Eq Weight forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Weight -> Weight -> Bool $c/= :: Weight -> Weight -> Bool == :: Weight -> Weight -> Bool $c== :: Weight -> Weight -> Bool Eq, Int -> Weight -> ShowS [Weight] -> ShowS Weight -> String (Int -> Weight -> ShowS) -> (Weight -> String) -> ([Weight] -> ShowS) -> Show Weight forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Weight] -> ShowS $cshowList :: [Weight] -> ShowS show :: Weight -> String $cshow :: Weight -> String showsPrec :: Int -> Weight -> ShowS $cshowsPrec :: Int -> Weight -> ShowS Show, Value -> Parser [Weight] Value -> Parser Weight (Value -> Parser Weight) -> (Value -> Parser [Weight]) -> FromJSON Weight forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [Weight] $cparseJSONList :: Value -> Parser [Weight] parseJSON :: Value -> Parser Weight $cparseJSON :: Value -> Parser Weight FromJSON, [Weight] -> Encoding [Weight] -> Value Weight -> Encoding Weight -> Value (Weight -> Value) -> (Weight -> Encoding) -> ([Weight] -> Value) -> ([Weight] -> Encoding) -> ToJSON Weight forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [Weight] -> Encoding $ctoEncodingList :: [Weight] -> Encoding toJSONList :: [Weight] -> Value $ctoJSONList :: [Weight] -> Value toEncoding :: Weight -> Encoding $ctoEncoding :: Weight -> Encoding toJSON :: Weight -> Value $ctoJSON :: Weight -> Value ToJSON) newtype Seed = Seed Float deriving (Seed -> Seed -> Bool (Seed -> Seed -> Bool) -> (Seed -> Seed -> Bool) -> Eq Seed forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Seed -> Seed -> Bool $c/= :: Seed -> Seed -> Bool == :: Seed -> Seed -> Bool $c== :: Seed -> Seed -> Bool Eq, Int -> Seed -> ShowS [Seed] -> ShowS Seed -> String (Int -> Seed -> ShowS) -> (Seed -> String) -> ([Seed] -> ShowS) -> Show Seed forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Seed] -> ShowS $cshowList :: [Seed] -> ShowS show :: Seed -> String $cshow :: Seed -> String showsPrec :: Int -> Seed -> ShowS $cshowsPrec :: Int -> Seed -> ShowS Show, Value -> Parser [Seed] Value -> Parser Seed (Value -> Parser Seed) -> (Value -> Parser [Seed]) -> FromJSON Seed forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [Seed] $cparseJSONList :: Value -> Parser [Seed] parseJSON :: Value -> Parser Seed $cparseJSON :: Value -> Parser Seed FromJSON, [Seed] -> Encoding [Seed] -> Value Seed -> Encoding Seed -> Value (Seed -> Value) -> (Seed -> Encoding) -> ([Seed] -> Value) -> ([Seed] -> Encoding) -> ToJSON Seed forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [Seed] -> Encoding $ctoEncodingList :: [Seed] -> Encoding toJSONList :: [Seed] -> Value $ctoJSONList :: [Seed] -> Value toEncoding :: Seed -> Encoding $ctoEncoding :: Seed -> Encoding toJSON :: Seed -> Value $ctoJSON :: Seed -> Value ToJSON) data FieldValueFactor = FieldValueFactor { FieldValueFactor -> FieldName fieldValueFactorField :: FieldName , FieldValueFactor -> Maybe Factor fieldValueFactor :: Maybe Factor , FieldValueFactor -> Maybe FactorModifier fieldValueFactorModifier :: Maybe FactorModifier , FieldValueFactor -> Maybe FactorMissingFieldValue fieldValueFactorMissing :: Maybe FactorMissingFieldValue } deriving (FieldValueFactor -> FieldValueFactor -> Bool (FieldValueFactor -> FieldValueFactor -> Bool) -> (FieldValueFactor -> FieldValueFactor -> Bool) -> Eq FieldValueFactor forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: FieldValueFactor -> FieldValueFactor -> Bool $c/= :: FieldValueFactor -> FieldValueFactor -> Bool == :: FieldValueFactor -> FieldValueFactor -> Bool $c== :: FieldValueFactor -> FieldValueFactor -> Bool Eq, Int -> FieldValueFactor -> ShowS [FieldValueFactor] -> ShowS FieldValueFactor -> String (Int -> FieldValueFactor -> ShowS) -> (FieldValueFactor -> String) -> ([FieldValueFactor] -> ShowS) -> Show FieldValueFactor forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [FieldValueFactor] -> ShowS $cshowList :: [FieldValueFactor] -> ShowS show :: FieldValueFactor -> String $cshow :: FieldValueFactor -> String showsPrec :: Int -> FieldValueFactor -> ShowS $cshowsPrec :: Int -> FieldValueFactor -> ShowS Show) newtype Factor = Factor Float deriving (Factor -> Factor -> Bool (Factor -> Factor -> Bool) -> (Factor -> Factor -> Bool) -> Eq Factor forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Factor -> Factor -> Bool $c/= :: Factor -> Factor -> Bool == :: Factor -> Factor -> Bool $c== :: Factor -> Factor -> Bool Eq, Int -> Factor -> ShowS [Factor] -> ShowS Factor -> String (Int -> Factor -> ShowS) -> (Factor -> String) -> ([Factor] -> ShowS) -> Show Factor forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Factor] -> ShowS $cshowList :: [Factor] -> ShowS show :: Factor -> String $cshow :: Factor -> String showsPrec :: Int -> Factor -> ShowS $cshowsPrec :: Int -> Factor -> ShowS Show, Value -> Parser [Factor] Value -> Parser Factor (Value -> Parser Factor) -> (Value -> Parser [Factor]) -> FromJSON Factor forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [Factor] $cparseJSONList :: Value -> Parser [Factor] parseJSON :: Value -> Parser Factor $cparseJSON :: Value -> Parser Factor FromJSON, [Factor] -> Encoding [Factor] -> Value Factor -> Encoding Factor -> Value (Factor -> Value) -> (Factor -> Encoding) -> ([Factor] -> Value) -> ([Factor] -> Encoding) -> ToJSON Factor forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [Factor] -> Encoding $ctoEncodingList :: [Factor] -> Encoding toJSONList :: [Factor] -> Value $ctoJSONList :: [Factor] -> Value toEncoding :: Factor -> Encoding $ctoEncoding :: Factor -> Encoding toJSON :: Factor -> Value $ctoJSON :: Factor -> Value ToJSON) data FactorModifier = FactorModifierNone | FactorModifierLog | FactorModifierLog1p | FactorModifierLog2p | FactorModifierLn | FactorModifierLn1p | FactorModifierLn2p | FactorModifierSquare | FactorModifierSqrt | FactorModifierReciprocal deriving (FactorModifier -> FactorModifier -> Bool (FactorModifier -> FactorModifier -> Bool) -> (FactorModifier -> FactorModifier -> Bool) -> Eq FactorModifier forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: FactorModifier -> FactorModifier -> Bool $c/= :: FactorModifier -> FactorModifier -> Bool == :: FactorModifier -> FactorModifier -> Bool $c== :: FactorModifier -> FactorModifier -> Bool Eq, Int -> FactorModifier -> ShowS [FactorModifier] -> ShowS FactorModifier -> String (Int -> FactorModifier -> ShowS) -> (FactorModifier -> String) -> ([FactorModifier] -> ShowS) -> Show FactorModifier forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [FactorModifier] -> ShowS $cshowList :: [FactorModifier] -> ShowS show :: FactorModifier -> String $cshow :: FactorModifier -> String showsPrec :: Int -> FactorModifier -> ShowS $cshowsPrec :: Int -> FactorModifier -> ShowS Show) newtype FactorMissingFieldValue = FactorMissingFieldValue Float deriving (FactorMissingFieldValue -> FactorMissingFieldValue -> Bool (FactorMissingFieldValue -> FactorMissingFieldValue -> Bool) -> (FactorMissingFieldValue -> FactorMissingFieldValue -> Bool) -> Eq FactorMissingFieldValue forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: FactorMissingFieldValue -> FactorMissingFieldValue -> Bool $c/= :: FactorMissingFieldValue -> FactorMissingFieldValue -> Bool == :: FactorMissingFieldValue -> FactorMissingFieldValue -> Bool $c== :: FactorMissingFieldValue -> FactorMissingFieldValue -> Bool Eq, Int -> FactorMissingFieldValue -> ShowS [FactorMissingFieldValue] -> ShowS FactorMissingFieldValue -> String (Int -> FactorMissingFieldValue -> ShowS) -> (FactorMissingFieldValue -> String) -> ([FactorMissingFieldValue] -> ShowS) -> Show FactorMissingFieldValue forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [FactorMissingFieldValue] -> ShowS $cshowList :: [FactorMissingFieldValue] -> ShowS show :: FactorMissingFieldValue -> String $cshow :: FactorMissingFieldValue -> String showsPrec :: Int -> FactorMissingFieldValue -> ShowS $cshowsPrec :: Int -> FactorMissingFieldValue -> ShowS Show, Value -> Parser [FactorMissingFieldValue] Value -> Parser FactorMissingFieldValue (Value -> Parser FactorMissingFieldValue) -> (Value -> Parser [FactorMissingFieldValue]) -> FromJSON FactorMissingFieldValue forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [FactorMissingFieldValue] $cparseJSONList :: Value -> Parser [FactorMissingFieldValue] parseJSON :: Value -> Parser FactorMissingFieldValue $cparseJSON :: Value -> Parser FactorMissingFieldValue FromJSON, [FactorMissingFieldValue] -> Encoding [FactorMissingFieldValue] -> Value FactorMissingFieldValue -> Encoding FactorMissingFieldValue -> Value (FactorMissingFieldValue -> Value) -> (FactorMissingFieldValue -> Encoding) -> ([FactorMissingFieldValue] -> Value) -> ([FactorMissingFieldValue] -> Encoding) -> ToJSON FactorMissingFieldValue forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [FactorMissingFieldValue] -> Encoding $ctoEncodingList :: [FactorMissingFieldValue] -> Encoding toJSONList :: [FactorMissingFieldValue] -> Value $ctoJSONList :: [FactorMissingFieldValue] -> Value toEncoding :: FactorMissingFieldValue -> Encoding $ctoEncoding :: FactorMissingFieldValue -> Encoding toJSON :: FactorMissingFieldValue -> Value $ctoJSON :: FactorMissingFieldValue -> Value ToJSON) instance ToJSON BoostMode where toJSON :: BoostMode -> Value toJSON BoostMode BoostModeMultiply = Value "multiply" toJSON BoostMode BoostModeReplace = Value "replace" toJSON BoostMode BoostModeSum = Value "sum" toJSON BoostMode BoostModeAvg = Value "avg" toJSON BoostMode BoostModeMax = Value "max" toJSON BoostMode BoostModeMin = Value "min" instance FromJSON BoostMode where parseJSON :: Value -> Parser BoostMode parseJSON = String -> (Text -> Parser BoostMode) -> Value -> Parser BoostMode forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "BoostMode" Text -> Parser BoostMode forall a (f :: * -> *). (Eq a, IsString a, MonadFail f, Show a) => a -> f BoostMode parse where parse :: a -> f BoostMode parse a "multiply" = BoostMode -> f BoostMode forall (f :: * -> *) a. Applicative f => a -> f a pure BoostMode BoostModeMultiply parse a "replace" = BoostMode -> f BoostMode forall (f :: * -> *) a. Applicative f => a -> f a pure BoostMode BoostModeReplace parse a "sum" = BoostMode -> f BoostMode forall (f :: * -> *) a. Applicative f => a -> f a pure BoostMode BoostModeSum parse a "avg" = BoostMode -> f BoostMode forall (f :: * -> *) a. Applicative f => a -> f a pure BoostMode BoostModeAvg parse a "max" = BoostMode -> f BoostMode forall (f :: * -> *) a. Applicative f => a -> f a pure BoostMode BoostModeMax parse a "min" = BoostMode -> f BoostMode forall (f :: * -> *) a. Applicative f => a -> f a pure BoostMode BoostModeMin parse a bm = String -> f BoostMode forall (m :: * -> *) a. MonadFail m => String -> m a fail (String "Unexpected BoostMode: " String -> ShowS forall a. Semigroup a => a -> a -> a <> a -> String forall a. Show a => a -> String show a bm) instance ToJSON ScoreMode where toJSON :: ScoreMode -> Value toJSON ScoreMode ScoreModeMultiply = Value "multiply" toJSON ScoreMode ScoreModeSum = Value "sum" toJSON ScoreMode ScoreModeFirst = Value "first" toJSON ScoreMode ScoreModeAvg = Value "avg" toJSON ScoreMode ScoreModeMax = Value "max" toJSON ScoreMode ScoreModeMin = Value "min" instance FromJSON ScoreMode where parseJSON :: Value -> Parser ScoreMode parseJSON = String -> (Text -> Parser ScoreMode) -> Value -> Parser ScoreMode forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "ScoreMode" Text -> Parser ScoreMode forall a (f :: * -> *). (Eq a, IsString a, MonadFail f, Show a) => a -> f ScoreMode parse where parse :: a -> f ScoreMode parse a "multiply" = ScoreMode -> f ScoreMode forall (f :: * -> *) a. Applicative f => a -> f a pure ScoreMode ScoreModeMultiply parse a "sum" = ScoreMode -> f ScoreMode forall (f :: * -> *) a. Applicative f => a -> f a pure ScoreMode ScoreModeSum parse a "first" = ScoreMode -> f ScoreMode forall (f :: * -> *) a. Applicative f => a -> f a pure ScoreMode ScoreModeFirst parse a "avg" = ScoreMode -> f ScoreMode forall (f :: * -> *) a. Applicative f => a -> f a pure ScoreMode ScoreModeAvg parse a "max" = ScoreMode -> f ScoreMode forall (f :: * -> *) a. Applicative f => a -> f a pure ScoreMode ScoreModeMax parse a "min" = ScoreMode -> f ScoreMode forall (f :: * -> *) a. Applicative f => a -> f a pure ScoreMode ScoreModeMin parse a sm = String -> f ScoreMode forall (m :: * -> *) a. MonadFail m => String -> m a fail (String "Unexpected ScoreMode: " String -> ShowS forall a. Semigroup a => a -> a -> a <> a -> String forall a. Show a => a -> String show a sm) functionScoreFunctionPair :: FunctionScoreFunction -> (Key, Value) functionScoreFunctionPair :: FunctionScoreFunction -> (Key, Value) functionScoreFunctionPair (FunctionScoreFunctionScript Script functionScoreScript) = (Key "script_score", Script -> Value forall a. ToJSON a => a -> Value toJSON Script functionScoreScript) functionScoreFunctionPair (FunctionScoreFunctionRandom Seed seed) = (Key "random_score", [(Key, Value)] -> Value omitNulls [ Key "seed" Key -> Seed -> (Key, Value) forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Seed seed ]) functionScoreFunctionPair (FunctionScoreFunctionFieldValueFactor FieldValueFactor fvf) = (Key "field_value_factor", FieldValueFactor -> Value forall a. ToJSON a => a -> Value toJSON FieldValueFactor fvf) parseFunctionScoreFunction :: Object -> Parser FunctionScoreFunction parseFunctionScoreFunction :: Object -> Parser FunctionScoreFunction parseFunctionScoreFunction Object o = Script -> Parser FunctionScoreFunction singleScript (Script -> Parser FunctionScoreFunction) -> Key -> Parser FunctionScoreFunction forall a b. FromJSON a => (a -> Parser b) -> Key -> Parser b `taggedWith` Key "script_score" Parser FunctionScoreFunction -> Parser FunctionScoreFunction -> Parser FunctionScoreFunction forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> Object -> Parser FunctionScoreFunction singleRandom (Object -> Parser FunctionScoreFunction) -> Key -> Parser FunctionScoreFunction forall a b. FromJSON a => (a -> Parser b) -> Key -> Parser b `taggedWith` Key "random_score" Parser FunctionScoreFunction -> Parser FunctionScoreFunction -> Parser FunctionScoreFunction forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> FieldValueFactor -> Parser FunctionScoreFunction singleFieldValueFactor (FieldValueFactor -> Parser FunctionScoreFunction) -> Key -> Parser FunctionScoreFunction forall a b. FromJSON a => (a -> Parser b) -> Key -> Parser b `taggedWith` Key "field_value_factor" where taggedWith :: (a -> Parser b) -> Key -> Parser b taggedWith a -> Parser b parser Key k = a -> Parser b parser (a -> Parser b) -> Parser a -> Parser b forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<< Object o Object -> Key -> Parser a forall a. FromJSON a => Object -> Key -> Parser a .: Key k singleScript :: Script -> Parser FunctionScoreFunction singleScript = FunctionScoreFunction -> Parser FunctionScoreFunction forall (f :: * -> *) a. Applicative f => a -> f a pure (FunctionScoreFunction -> Parser FunctionScoreFunction) -> (Script -> FunctionScoreFunction) -> Script -> Parser FunctionScoreFunction forall b c a. (b -> c) -> (a -> b) -> a -> c . Script -> FunctionScoreFunction FunctionScoreFunctionScript singleRandom :: Object -> Parser FunctionScoreFunction singleRandom Object o' = Seed -> FunctionScoreFunction FunctionScoreFunctionRandom (Seed -> FunctionScoreFunction) -> Parser Seed -> Parser FunctionScoreFunction forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o' Object -> Key -> Parser Seed forall a. FromJSON a => Object -> Key -> Parser a .: Key "seed" singleFieldValueFactor :: FieldValueFactor -> Parser FunctionScoreFunction singleFieldValueFactor = FunctionScoreFunction -> Parser FunctionScoreFunction forall (f :: * -> *) a. Applicative f => a -> f a pure (FunctionScoreFunction -> Parser FunctionScoreFunction) -> (FieldValueFactor -> FunctionScoreFunction) -> FieldValueFactor -> Parser FunctionScoreFunction forall b c a. (b -> c) -> (a -> b) -> a -> c . FieldValueFactor -> FunctionScoreFunction FunctionScoreFunctionFieldValueFactor instance ToJSON ScriptFields where toJSON :: ScriptFields -> Value toJSON (ScriptFields Object x) = Object -> Value Object Object x instance FromJSON ScriptFields where parseJSON :: Value -> Parser ScriptFields parseJSON (Object Object o) = ScriptFields -> Parser ScriptFields forall (f :: * -> *) a. Applicative f => a -> f a pure (Object -> ScriptFields ScriptFields Object o) parseJSON Value _ = String -> Parser ScriptFields forall (m :: * -> *) a. MonadFail m => String -> m a fail String "error parsing ScriptFields" instance ToJSON Script where toJSON :: Script -> Value toJSON Script script = [(Key, Value)] -> Value object [ Key "script" Key -> Value -> (Key, Value) forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= [(Key, Value)] -> Value omitNulls (Script -> [(Key, Value)] forall a. KeyValue a => Script -> [a] base Script script) ] where base :: Script -> [a] base (Script Maybe ScriptLanguage lang (ScriptInline Text source) Maybe ScriptParams params) = [Key "lang" Key -> Maybe ScriptLanguage -> a forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe ScriptLanguage lang, Key "source" Key -> Text -> a forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Text source, Key "params" Key -> Maybe ScriptParams -> a forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe ScriptParams params] base (Script Maybe ScriptLanguage lang (ScriptId Text id_) Maybe ScriptParams params) = [Key "lang" Key -> Maybe ScriptLanguage -> a forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe ScriptLanguage lang, Key "id" Key -> Text -> a forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Text id_, Key "params" Key -> Maybe ScriptParams -> a forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe ScriptParams params] instance FromJSON Script where parseJSON :: Value -> Parser Script parseJSON = String -> (Object -> Parser Script) -> Value -> Parser Script forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "Script" Object -> Parser Script parse where parseSource :: Object -> Parser ScriptSource parseSource Object o = do Maybe Text inline <- Object o Object -> Key -> Parser (Maybe Text) forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "source" Maybe Text id_ <- Object o Object -> Key -> Parser (Maybe Text) forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "id" ScriptSource -> Parser ScriptSource forall (m :: * -> *) a. Monad m => a -> m a return (ScriptSource -> Parser ScriptSource) -> ScriptSource -> Parser ScriptSource forall a b. (a -> b) -> a -> b $ case (Maybe Text inline,Maybe Text id_) of (Just Text x,Maybe Text Nothing) -> Text -> ScriptSource ScriptInline Text x (Maybe Text Nothing,Just Text x) -> Text -> ScriptSource ScriptId Text x (Maybe Text Nothing,Maybe Text Nothing) -> String -> ScriptSource forall a. HasCallStack => String -> a error String "Script has to be either stored or inlined" (Just Text _,Just Text _) -> String -> ScriptSource forall a. HasCallStack => String -> a error String "Script can't both be stored and inlined at the same time" parse :: Object -> Parser Script parse Object o = Object o Object -> Key -> Parser Object forall a. FromJSON a => Object -> Key -> Parser a .: Key "script" Parser Object -> (Object -> Parser Script) -> Parser Script forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \Object o' -> Maybe ScriptLanguage -> ScriptSource -> Maybe ScriptParams -> Script Script (Maybe ScriptLanguage -> ScriptSource -> Maybe ScriptParams -> Script) -> Parser (Maybe ScriptLanguage) -> Parser (ScriptSource -> Maybe ScriptParams -> Script) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o' Object -> Key -> Parser (Maybe ScriptLanguage) forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "lang" Parser (ScriptSource -> Maybe ScriptParams -> Script) -> Parser ScriptSource -> Parser (Maybe ScriptParams -> Script) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object -> Parser ScriptSource parseSource Object o' Parser (Maybe ScriptParams -> Script) -> Parser (Maybe ScriptParams) -> Parser Script forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o' Object -> Key -> Parser (Maybe ScriptParams) forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "params" instance ToJSON ScriptParams where toJSON :: ScriptParams -> Value toJSON (ScriptParams Object x) = Object -> Value Object Object x instance FromJSON ScriptParams where parseJSON :: Value -> Parser ScriptParams parseJSON (Object Object o) = ScriptParams -> Parser ScriptParams forall (f :: * -> *) a. Applicative f => a -> f a pure (Object -> ScriptParams ScriptParams Object o) parseJSON Value _ = String -> Parser ScriptParams forall (m :: * -> *) a. MonadFail m => String -> m a fail String "error parsing ScriptParams" instance ToJSON FieldValueFactor where toJSON :: FieldValueFactor -> Value toJSON (FieldValueFactor FieldName field Maybe Factor factor Maybe FactorModifier modifier Maybe FactorMissingFieldValue missing) = [(Key, Value)] -> Value omitNulls [(Key, Value)] base where base :: [(Key, Value)] base = [ Key "field" Key -> FieldName -> (Key, Value) forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= FieldName field , Key "factor" Key -> Maybe Factor -> (Key, Value) forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe Factor factor , Key "modifier" Key -> Maybe FactorModifier -> (Key, Value) forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe FactorModifier modifier , Key "missing" Key -> Maybe FactorMissingFieldValue -> (Key, Value) forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe FactorMissingFieldValue missing ] instance FromJSON FieldValueFactor where parseJSON :: Value -> Parser FieldValueFactor parseJSON = String -> (Object -> Parser FieldValueFactor) -> Value -> Parser FieldValueFactor forall a. String -> (Object -> Parser a) -> Value -> Parser a withObject String "FieldValueFactor" Object -> Parser FieldValueFactor parse where parse :: Object -> Parser FieldValueFactor parse Object o = FieldName -> Maybe Factor -> Maybe FactorModifier -> Maybe FactorMissingFieldValue -> FieldValueFactor FieldValueFactor (FieldName -> Maybe Factor -> Maybe FactorModifier -> Maybe FactorMissingFieldValue -> FieldValueFactor) -> Parser FieldName -> Parser (Maybe Factor -> Maybe FactorModifier -> Maybe FactorMissingFieldValue -> FieldValueFactor) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object o Object -> Key -> Parser FieldName forall a. FromJSON a => Object -> Key -> Parser a .: Key "field" Parser (Maybe Factor -> Maybe FactorModifier -> Maybe FactorMissingFieldValue -> FieldValueFactor) -> Parser (Maybe Factor) -> Parser (Maybe FactorModifier -> Maybe FactorMissingFieldValue -> FieldValueFactor) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Key -> Parser (Maybe Factor) forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "factor" Parser (Maybe FactorModifier -> Maybe FactorMissingFieldValue -> FieldValueFactor) -> Parser (Maybe FactorModifier) -> Parser (Maybe FactorMissingFieldValue -> FieldValueFactor) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Key -> Parser (Maybe FactorModifier) forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "modifier" Parser (Maybe FactorMissingFieldValue -> FieldValueFactor) -> Parser (Maybe FactorMissingFieldValue) -> Parser FieldValueFactor forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object o Object -> Key -> Parser (Maybe FactorMissingFieldValue) forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "missing" instance ToJSON FactorModifier where toJSON :: FactorModifier -> Value toJSON FactorModifier FactorModifierNone = Value "none" toJSON FactorModifier FactorModifierLog = Value "log" toJSON FactorModifier FactorModifierLog1p = Value "log1p" toJSON FactorModifier FactorModifierLog2p = Value "log2p" toJSON FactorModifier FactorModifierLn = Value "ln" toJSON FactorModifier FactorModifierLn1p = Value "ln1p" toJSON FactorModifier FactorModifierLn2p = Value "ln2p" toJSON FactorModifier FactorModifierSquare = Value "square" toJSON FactorModifier FactorModifierSqrt = Value "sqrt" toJSON FactorModifier FactorModifierReciprocal = Value "reciprocal" instance FromJSON FactorModifier where parseJSON :: Value -> Parser FactorModifier parseJSON = String -> (Text -> Parser FactorModifier) -> Value -> Parser FactorModifier forall a. String -> (Text -> Parser a) -> Value -> Parser a withText String "FactorModifier" Text -> Parser FactorModifier forall a (f :: * -> *). (Eq a, IsString a, MonadFail f, Show a) => a -> f FactorModifier parse where parse :: a -> f FactorModifier parse a "none" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierNone parse a "log" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierLog parse a "log1p" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierLog1p parse a "log2p" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierLog2p parse a "ln" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierLn parse a "ln1p" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierLn1p parse a "ln2p" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierLn2p parse a "square" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierSquare parse a "sqrt" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierSqrt parse a "reciprocal" = FactorModifier -> f FactorModifier forall (f :: * -> *) a. Applicative f => a -> f a pure FactorModifier FactorModifierReciprocal parse a fm = String -> f FactorModifier forall (m :: * -> *) a. MonadFail m => String -> m a fail (String "Unexpected FactorModifier: " String -> ShowS forall a. Semigroup a => a -> a -> a <> a -> String forall a. Show a => a -> String show a fm)