{-# LANGUAGE OverloadedStrings #-}
module Database.Bloodhound.Internal.Versions.Common.Types.Query.Range
( GreaterThan (..),
GreaterThanD (..),
GreaterThanEq (..),
GreaterThanEqD (..),
LessThan (..),
LessThanD (..),
LessThanEq (..),
LessThanEqD (..),
RangeQuery (..),
RangeValue (..),
mkRangeQuery,
rangeQueryFieldLens,
rangeQueryRangeLens,
rangeQueryBoostLens,
)
where
import Database.Bloodhound.Internal.Utils.Imports
import Database.Bloodhound.Internal.Versions.Common.Types.Newtypes
import Database.Bloodhound.Internal.Versions.Common.Types.Query.Commons
import GHC.Generics
data RangeQuery = RangeQuery
{ RangeQuery -> FieldName
rangeQueryField :: FieldName,
RangeQuery -> RangeValue
rangeQueryRange :: RangeValue,
RangeQuery -> Boost
rangeQueryBoost :: Boost
}
deriving stock (RangeQuery -> RangeQuery -> Bool
(RangeQuery -> RangeQuery -> Bool)
-> (RangeQuery -> RangeQuery -> Bool) -> Eq RangeQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RangeQuery -> RangeQuery -> Bool
== :: RangeQuery -> RangeQuery -> Bool
$c/= :: RangeQuery -> RangeQuery -> Bool
/= :: RangeQuery -> RangeQuery -> Bool
Eq, Int -> RangeQuery -> ShowS
[RangeQuery] -> ShowS
RangeQuery -> String
(Int -> RangeQuery -> ShowS)
-> (RangeQuery -> String)
-> ([RangeQuery] -> ShowS)
-> Show RangeQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RangeQuery -> ShowS
showsPrec :: Int -> RangeQuery -> ShowS
$cshow :: RangeQuery -> String
show :: RangeQuery -> String
$cshowList :: [RangeQuery] -> ShowS
showList :: [RangeQuery] -> ShowS
Show, (forall x. RangeQuery -> Rep RangeQuery x)
-> (forall x. Rep RangeQuery x -> RangeQuery) -> Generic RangeQuery
forall x. Rep RangeQuery x -> RangeQuery
forall x. RangeQuery -> Rep RangeQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RangeQuery -> Rep RangeQuery x
from :: forall x. RangeQuery -> Rep RangeQuery x
$cto :: forall x. Rep RangeQuery x -> RangeQuery
to :: forall x. Rep RangeQuery x -> RangeQuery
Generic)
rangeQueryFieldLens :: Lens' RangeQuery FieldName
rangeQueryFieldLens :: Lens' RangeQuery FieldName
rangeQueryFieldLens = (RangeQuery -> FieldName)
-> (RangeQuery -> FieldName -> RangeQuery)
-> Lens' RangeQuery FieldName
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens RangeQuery -> FieldName
rangeQueryField (\RangeQuery
x FieldName
y -> RangeQuery
x {rangeQueryField = y})
rangeQueryRangeLens :: Lens' RangeQuery RangeValue
rangeQueryRangeLens :: Lens' RangeQuery RangeValue
rangeQueryRangeLens = (RangeQuery -> RangeValue)
-> (RangeQuery -> RangeValue -> RangeQuery)
-> Lens' RangeQuery RangeValue
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens RangeQuery -> RangeValue
rangeQueryRange (\RangeQuery
x RangeValue
y -> RangeQuery
x {rangeQueryRange = y})
rangeQueryBoostLens :: Lens' RangeQuery Boost
rangeQueryBoostLens :: Lens' RangeQuery Boost
rangeQueryBoostLens = (RangeQuery -> Boost)
-> (RangeQuery -> Boost -> RangeQuery) -> Lens' RangeQuery Boost
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens RangeQuery -> Boost
rangeQueryBoost (\RangeQuery
x Boost
y -> RangeQuery
x {rangeQueryBoost = y})
instance ToJSON RangeQuery where
toJSON :: RangeQuery -> Value
toJSON (RangeQuery (FieldName Text
fieldName) RangeValue
range Boost
boost) =
[Pair] -> Value
object [Text -> Key
fromText Text
fieldName Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
object [Pair]
conjoined]
where
conjoined :: [Pair]
conjoined = (Key
"boost" Key -> Boost -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Boost
boost) Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: RangeValue -> [Pair]
rangeValueToPair RangeValue
range
instance FromJSON RangeQuery where
parseJSON :: Value -> Parser RangeQuery
parseJSON = String
-> (Object -> Parser RangeQuery) -> Value -> Parser RangeQuery
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RangeQuery" Object -> Parser RangeQuery
parse
where
parse :: Object -> Parser RangeQuery
parse = (FieldName -> Object -> Parser RangeQuery)
-> Object -> Parser RangeQuery
forall (m :: * -> *) a.
(Monad m, MonadFail m) =>
(FieldName -> Object -> m a) -> Object -> m a
fieldTagged ((FieldName -> Object -> Parser RangeQuery)
-> Object -> Parser RangeQuery)
-> (FieldName -> Object -> Parser RangeQuery)
-> Object
-> Parser RangeQuery
forall a b. (a -> b) -> a -> b
$ \FieldName
fn Object
o ->
FieldName -> RangeValue -> Boost -> RangeQuery
RangeQuery FieldName
fn
(RangeValue -> Boost -> RangeQuery)
-> Parser RangeValue -> Parser (Boost -> RangeQuery)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser RangeValue
forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
o)
Parser (Boost -> RangeQuery) -> Parser Boost -> Parser RangeQuery
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Boost
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"boost"
mkRangeQuery :: FieldName -> RangeValue -> RangeQuery
mkRangeQuery :: FieldName -> RangeValue -> RangeQuery
mkRangeQuery FieldName
f RangeValue
r = FieldName -> RangeValue -> Boost -> RangeQuery
RangeQuery FieldName
f RangeValue
r (Double -> Boost
Boost Double
1.0)
newtype LessThan = LessThan Double deriving stock (LessThan -> LessThan -> Bool
(LessThan -> LessThan -> Bool)
-> (LessThan -> LessThan -> Bool) -> Eq LessThan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LessThan -> LessThan -> Bool
== :: LessThan -> LessThan -> Bool
$c/= :: LessThan -> LessThan -> Bool
/= :: LessThan -> LessThan -> Bool
Eq, Int -> LessThan -> ShowS
[LessThan] -> ShowS
LessThan -> String
(Int -> LessThan -> ShowS)
-> (LessThan -> String) -> ([LessThan] -> ShowS) -> Show LessThan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LessThan -> ShowS
showsPrec :: Int -> LessThan -> ShowS
$cshow :: LessThan -> String
show :: LessThan -> String
$cshowList :: [LessThan] -> ShowS
showList :: [LessThan] -> ShowS
Show, (forall x. LessThan -> Rep LessThan x)
-> (forall x. Rep LessThan x -> LessThan) -> Generic LessThan
forall x. Rep LessThan x -> LessThan
forall x. LessThan -> Rep LessThan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LessThan -> Rep LessThan x
from :: forall x. LessThan -> Rep LessThan x
$cto :: forall x. Rep LessThan x -> LessThan
to :: forall x. Rep LessThan x -> LessThan
Generic)
newtype LessThanEq = LessThanEq Double deriving stock (LessThanEq -> LessThanEq -> Bool
(LessThanEq -> LessThanEq -> Bool)
-> (LessThanEq -> LessThanEq -> Bool) -> Eq LessThanEq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LessThanEq -> LessThanEq -> Bool
== :: LessThanEq -> LessThanEq -> Bool
$c/= :: LessThanEq -> LessThanEq -> Bool
/= :: LessThanEq -> LessThanEq -> Bool
Eq, Int -> LessThanEq -> ShowS
[LessThanEq] -> ShowS
LessThanEq -> String
(Int -> LessThanEq -> ShowS)
-> (LessThanEq -> String)
-> ([LessThanEq] -> ShowS)
-> Show LessThanEq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LessThanEq -> ShowS
showsPrec :: Int -> LessThanEq -> ShowS
$cshow :: LessThanEq -> String
show :: LessThanEq -> String
$cshowList :: [LessThanEq] -> ShowS
showList :: [LessThanEq] -> ShowS
Show, (forall x. LessThanEq -> Rep LessThanEq x)
-> (forall x. Rep LessThanEq x -> LessThanEq) -> Generic LessThanEq
forall x. Rep LessThanEq x -> LessThanEq
forall x. LessThanEq -> Rep LessThanEq x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LessThanEq -> Rep LessThanEq x
from :: forall x. LessThanEq -> Rep LessThanEq x
$cto :: forall x. Rep LessThanEq x -> LessThanEq
to :: forall x. Rep LessThanEq x -> LessThanEq
Generic)
newtype GreaterThan = GreaterThan Double deriving stock (GreaterThan -> GreaterThan -> Bool
(GreaterThan -> GreaterThan -> Bool)
-> (GreaterThan -> GreaterThan -> Bool) -> Eq GreaterThan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GreaterThan -> GreaterThan -> Bool
== :: GreaterThan -> GreaterThan -> Bool
$c/= :: GreaterThan -> GreaterThan -> Bool
/= :: GreaterThan -> GreaterThan -> Bool
Eq, Int -> GreaterThan -> ShowS
[GreaterThan] -> ShowS
GreaterThan -> String
(Int -> GreaterThan -> ShowS)
-> (GreaterThan -> String)
-> ([GreaterThan] -> ShowS)
-> Show GreaterThan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GreaterThan -> ShowS
showsPrec :: Int -> GreaterThan -> ShowS
$cshow :: GreaterThan -> String
show :: GreaterThan -> String
$cshowList :: [GreaterThan] -> ShowS
showList :: [GreaterThan] -> ShowS
Show, (forall x. GreaterThan -> Rep GreaterThan x)
-> (forall x. Rep GreaterThan x -> GreaterThan)
-> Generic GreaterThan
forall x. Rep GreaterThan x -> GreaterThan
forall x. GreaterThan -> Rep GreaterThan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GreaterThan -> Rep GreaterThan x
from :: forall x. GreaterThan -> Rep GreaterThan x
$cto :: forall x. Rep GreaterThan x -> GreaterThan
to :: forall x. Rep GreaterThan x -> GreaterThan
Generic)
newtype GreaterThanEq = GreaterThanEq Double deriving stock (GreaterThanEq -> GreaterThanEq -> Bool
(GreaterThanEq -> GreaterThanEq -> Bool)
-> (GreaterThanEq -> GreaterThanEq -> Bool) -> Eq GreaterThanEq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GreaterThanEq -> GreaterThanEq -> Bool
== :: GreaterThanEq -> GreaterThanEq -> Bool
$c/= :: GreaterThanEq -> GreaterThanEq -> Bool
/= :: GreaterThanEq -> GreaterThanEq -> Bool
Eq, Int -> GreaterThanEq -> ShowS
[GreaterThanEq] -> ShowS
GreaterThanEq -> String
(Int -> GreaterThanEq -> ShowS)
-> (GreaterThanEq -> String)
-> ([GreaterThanEq] -> ShowS)
-> Show GreaterThanEq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GreaterThanEq -> ShowS
showsPrec :: Int -> GreaterThanEq -> ShowS
$cshow :: GreaterThanEq -> String
show :: GreaterThanEq -> String
$cshowList :: [GreaterThanEq] -> ShowS
showList :: [GreaterThanEq] -> ShowS
Show, (forall x. GreaterThanEq -> Rep GreaterThanEq x)
-> (forall x. Rep GreaterThanEq x -> GreaterThanEq)
-> Generic GreaterThanEq
forall x. Rep GreaterThanEq x -> GreaterThanEq
forall x. GreaterThanEq -> Rep GreaterThanEq x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GreaterThanEq -> Rep GreaterThanEq x
from :: forall x. GreaterThanEq -> Rep GreaterThanEq x
$cto :: forall x. Rep GreaterThanEq x -> GreaterThanEq
to :: forall x. Rep GreaterThanEq x -> GreaterThanEq
Generic)
newtype LessThanD = LessThanD UTCTime deriving stock (LessThanD -> LessThanD -> Bool
(LessThanD -> LessThanD -> Bool)
-> (LessThanD -> LessThanD -> Bool) -> Eq LessThanD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LessThanD -> LessThanD -> Bool
== :: LessThanD -> LessThanD -> Bool
$c/= :: LessThanD -> LessThanD -> Bool
/= :: LessThanD -> LessThanD -> Bool
Eq, Int -> LessThanD -> ShowS
[LessThanD] -> ShowS
LessThanD -> String
(Int -> LessThanD -> ShowS)
-> (LessThanD -> String)
-> ([LessThanD] -> ShowS)
-> Show LessThanD
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LessThanD -> ShowS
showsPrec :: Int -> LessThanD -> ShowS
$cshow :: LessThanD -> String
show :: LessThanD -> String
$cshowList :: [LessThanD] -> ShowS
showList :: [LessThanD] -> ShowS
Show, (forall x. LessThanD -> Rep LessThanD x)
-> (forall x. Rep LessThanD x -> LessThanD) -> Generic LessThanD
forall x. Rep LessThanD x -> LessThanD
forall x. LessThanD -> Rep LessThanD x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LessThanD -> Rep LessThanD x
from :: forall x. LessThanD -> Rep LessThanD x
$cto :: forall x. Rep LessThanD x -> LessThanD
to :: forall x. Rep LessThanD x -> LessThanD
Generic)
newtype LessThanEqD = LessThanEqD UTCTime deriving stock (LessThanEqD -> LessThanEqD -> Bool
(LessThanEqD -> LessThanEqD -> Bool)
-> (LessThanEqD -> LessThanEqD -> Bool) -> Eq LessThanEqD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LessThanEqD -> LessThanEqD -> Bool
== :: LessThanEqD -> LessThanEqD -> Bool
$c/= :: LessThanEqD -> LessThanEqD -> Bool
/= :: LessThanEqD -> LessThanEqD -> Bool
Eq, Int -> LessThanEqD -> ShowS
[LessThanEqD] -> ShowS
LessThanEqD -> String
(Int -> LessThanEqD -> ShowS)
-> (LessThanEqD -> String)
-> ([LessThanEqD] -> ShowS)
-> Show LessThanEqD
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LessThanEqD -> ShowS
showsPrec :: Int -> LessThanEqD -> ShowS
$cshow :: LessThanEqD -> String
show :: LessThanEqD -> String
$cshowList :: [LessThanEqD] -> ShowS
showList :: [LessThanEqD] -> ShowS
Show, (forall x. LessThanEqD -> Rep LessThanEqD x)
-> (forall x. Rep LessThanEqD x -> LessThanEqD)
-> Generic LessThanEqD
forall x. Rep LessThanEqD x -> LessThanEqD
forall x. LessThanEqD -> Rep LessThanEqD x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LessThanEqD -> Rep LessThanEqD x
from :: forall x. LessThanEqD -> Rep LessThanEqD x
$cto :: forall x. Rep LessThanEqD x -> LessThanEqD
to :: forall x. Rep LessThanEqD x -> LessThanEqD
Generic)
newtype GreaterThanD = GreaterThanD UTCTime deriving stock (GreaterThanD -> GreaterThanD -> Bool
(GreaterThanD -> GreaterThanD -> Bool)
-> (GreaterThanD -> GreaterThanD -> Bool) -> Eq GreaterThanD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GreaterThanD -> GreaterThanD -> Bool
== :: GreaterThanD -> GreaterThanD -> Bool
$c/= :: GreaterThanD -> GreaterThanD -> Bool
/= :: GreaterThanD -> GreaterThanD -> Bool
Eq, Int -> GreaterThanD -> ShowS
[GreaterThanD] -> ShowS
GreaterThanD -> String
(Int -> GreaterThanD -> ShowS)
-> (GreaterThanD -> String)
-> ([GreaterThanD] -> ShowS)
-> Show GreaterThanD
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GreaterThanD -> ShowS
showsPrec :: Int -> GreaterThanD -> ShowS
$cshow :: GreaterThanD -> String
show :: GreaterThanD -> String
$cshowList :: [GreaterThanD] -> ShowS
showList :: [GreaterThanD] -> ShowS
Show, (forall x. GreaterThanD -> Rep GreaterThanD x)
-> (forall x. Rep GreaterThanD x -> GreaterThanD)
-> Generic GreaterThanD
forall x. Rep GreaterThanD x -> GreaterThanD
forall x. GreaterThanD -> Rep GreaterThanD x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GreaterThanD -> Rep GreaterThanD x
from :: forall x. GreaterThanD -> Rep GreaterThanD x
$cto :: forall x. Rep GreaterThanD x -> GreaterThanD
to :: forall x. Rep GreaterThanD x -> GreaterThanD
Generic)
newtype GreaterThanEqD = GreaterThanEqD UTCTime deriving stock (GreaterThanEqD -> GreaterThanEqD -> Bool
(GreaterThanEqD -> GreaterThanEqD -> Bool)
-> (GreaterThanEqD -> GreaterThanEqD -> Bool) -> Eq GreaterThanEqD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GreaterThanEqD -> GreaterThanEqD -> Bool
== :: GreaterThanEqD -> GreaterThanEqD -> Bool
$c/= :: GreaterThanEqD -> GreaterThanEqD -> Bool
/= :: GreaterThanEqD -> GreaterThanEqD -> Bool
Eq, Int -> GreaterThanEqD -> ShowS
[GreaterThanEqD] -> ShowS
GreaterThanEqD -> String
(Int -> GreaterThanEqD -> ShowS)
-> (GreaterThanEqD -> String)
-> ([GreaterThanEqD] -> ShowS)
-> Show GreaterThanEqD
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GreaterThanEqD -> ShowS
showsPrec :: Int -> GreaterThanEqD -> ShowS
$cshow :: GreaterThanEqD -> String
show :: GreaterThanEqD -> String
$cshowList :: [GreaterThanEqD] -> ShowS
showList :: [GreaterThanEqD] -> ShowS
Show, (forall x. GreaterThanEqD -> Rep GreaterThanEqD x)
-> (forall x. Rep GreaterThanEqD x -> GreaterThanEqD)
-> Generic GreaterThanEqD
forall x. Rep GreaterThanEqD x -> GreaterThanEqD
forall x. GreaterThanEqD -> Rep GreaterThanEqD x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GreaterThanEqD -> Rep GreaterThanEqD x
from :: forall x. GreaterThanEqD -> Rep GreaterThanEqD x
$cto :: forall x. Rep GreaterThanEqD x -> GreaterThanEqD
to :: forall x. Rep GreaterThanEqD x -> GreaterThanEqD
Generic)
data RangeValue
= RangeDateLte LessThanEqD
| RangeDateLt LessThanD
| RangeDateGte GreaterThanEqD
| RangeDateGt GreaterThanD
| RangeDateGtLt GreaterThanD LessThanD
| RangeDateGteLte GreaterThanEqD LessThanEqD
| RangeDateGteLt GreaterThanEqD LessThanD
| RangeDateGtLte GreaterThanD LessThanEqD
| RangeDoubleLte LessThanEq
| RangeDoubleLt LessThan
| RangeDoubleGte GreaterThanEq
| RangeDoubleGt GreaterThan
| RangeDoubleGtLt GreaterThan LessThan
| RangeDoubleGteLte GreaterThanEq LessThanEq
| RangeDoubleGteLt GreaterThanEq LessThan
| RangeDoubleGtLte GreaterThan LessThanEq
deriving stock (RangeValue -> RangeValue -> Bool
(RangeValue -> RangeValue -> Bool)
-> (RangeValue -> RangeValue -> Bool) -> Eq RangeValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RangeValue -> RangeValue -> Bool
== :: RangeValue -> RangeValue -> Bool
$c/= :: RangeValue -> RangeValue -> Bool
/= :: RangeValue -> RangeValue -> Bool
Eq, Int -> RangeValue -> ShowS
[RangeValue] -> ShowS
RangeValue -> String
(Int -> RangeValue -> ShowS)
-> (RangeValue -> String)
-> ([RangeValue] -> ShowS)
-> Show RangeValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RangeValue -> ShowS
showsPrec :: Int -> RangeValue -> ShowS
$cshow :: RangeValue -> String
show :: RangeValue -> String
$cshowList :: [RangeValue] -> ShowS
showList :: [RangeValue] -> ShowS
Show, (forall x. RangeValue -> Rep RangeValue x)
-> (forall x. Rep RangeValue x -> RangeValue) -> Generic RangeValue
forall x. Rep RangeValue x -> RangeValue
forall x. RangeValue -> Rep RangeValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RangeValue -> Rep RangeValue x
from :: forall x. RangeValue -> Rep RangeValue x
$cto :: forall x. Rep RangeValue x -> RangeValue
to :: forall x. Rep RangeValue x -> RangeValue
Generic)
parseRangeValue ::
( FromJSON t4,
FromJSON t3,
FromJSON t2,
FromJSON t1
) =>
(t3 -> t5) ->
(t1 -> t6) ->
(t4 -> t7) ->
(t2 -> t8) ->
(t5 -> t6 -> b) ->
(t7 -> t6 -> b) ->
(t5 -> t8 -> b) ->
(t7 -> t8 -> b) ->
(t5 -> b) ->
(t6 -> b) ->
(t7 -> b) ->
(t8 -> b) ->
Parser b ->
Object ->
Parser b
parseRangeValue :: forall t4 t3 t2 t1 t5 t6 t7 t8 b.
(FromJSON t4, FromJSON t3, FromJSON t2, FromJSON t1) =>
(t3 -> t5)
-> (t1 -> t6)
-> (t4 -> t7)
-> (t2 -> t8)
-> (t5 -> t6 -> b)
-> (t7 -> t6 -> b)
-> (t5 -> t8 -> b)
-> (t7 -> t8 -> b)
-> (t5 -> b)
-> (t6 -> b)
-> (t7 -> b)
-> (t8 -> b)
-> Parser b
-> Object
-> Parser b
parseRangeValue
t3 -> t5
mkGt
t1 -> t6
mkLt
t4 -> t7
mkGte
t2 -> t8
mkLte
t5 -> t6 -> b
fGtLt
t7 -> t6 -> b
fGteLt
t5 -> t8 -> b
fGtLte
t7 -> t8 -> b
fGteLte
t5 -> b
fGt
t6 -> b
fLt
t7 -> b
fGte
t8 -> b
fLte
Parser b
nada
Object
o = do
Maybe t1
lt <- Object
o Object -> Key -> Parser (Maybe t1)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"lt"
Maybe t2
lte <- Object
o Object -> Key -> Parser (Maybe t2)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"lte"
Maybe t3
gt <- Object
o Object -> Key -> Parser (Maybe t3)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"gt"
Maybe t4
gte <- Object
o Object -> Key -> Parser (Maybe t4)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"gte"
case (Maybe t1
lt, Maybe t2
lte, Maybe t3
gt, Maybe t4
gte) of
(Just t1
a, Maybe t2
_, Just t3
b, Maybe t4
_) ->
b -> Parser b
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (t5 -> t6 -> b
fGtLt (t3 -> t5
mkGt t3
b) (t1 -> t6
mkLt t1
a))
(Just t1
a, Maybe t2
_, Maybe t3
_, Just t4
b) ->
b -> Parser b
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (t7 -> t6 -> b
fGteLt (t4 -> t7
mkGte t4
b) (t1 -> t6
mkLt t1
a))
(Maybe t1
_, Just t2
a, Just t3
b, Maybe t4
_) ->
b -> Parser b
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (t5 -> t8 -> b
fGtLte (t3 -> t5
mkGt t3
b) (t2 -> t8
mkLte t2
a))
(Maybe t1
_, Just t2
a, Maybe t3
_, Just t4
b) ->
b -> Parser b
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (t7 -> t8 -> b
fGteLte (t4 -> t7
mkGte t4
b) (t2 -> t8
mkLte t2
a))
(Maybe t1
_, Maybe t2
_, Just t3
a, Maybe t4
_) ->
b -> Parser b
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (t5 -> b
fGt (t3 -> t5
mkGt t3
a))
(Just t1
a, Maybe t2
_, Maybe t3
_, Maybe t4
_) ->
b -> Parser b
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (t6 -> b
fLt (t1 -> t6
mkLt t1
a))
(Maybe t1
_, Maybe t2
_, Maybe t3
_, Just t4
a) ->
b -> Parser b
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (t7 -> b
fGte (t4 -> t7
mkGte t4
a))
(Maybe t1
_, Just t2
a, Maybe t3
_, Maybe t4
_) ->
b -> Parser b
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (t8 -> b
fLte (t2 -> t8
mkLte t2
a))
(Maybe t1
Nothing, Maybe t2
Nothing, Maybe t3
Nothing, Maybe t4
Nothing) ->
Parser b
nada
instance FromJSON RangeValue where
parseJSON :: Value -> Parser RangeValue
parseJSON = String
-> (Object -> Parser RangeValue) -> Value -> Parser RangeValue
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RangeValue" Object -> Parser RangeValue
parse
where
parse :: Object -> Parser RangeValue
parse Object
o =
Object -> Parser RangeValue
parseDate Object
o
Parser RangeValue -> Parser RangeValue -> Parser RangeValue
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Object -> Parser RangeValue
parseDouble Object
o
parseDate :: Object -> Parser RangeValue
parseDate Object
o =
(UTCTime -> GreaterThanD)
-> (UTCTime -> LessThanD)
-> (UTCTime -> GreaterThanEqD)
-> (UTCTime -> LessThanEqD)
-> (GreaterThanD -> LessThanD -> RangeValue)
-> (GreaterThanEqD -> LessThanD -> RangeValue)
-> (GreaterThanD -> LessThanEqD -> RangeValue)
-> (GreaterThanEqD -> LessThanEqD -> RangeValue)
-> (GreaterThanD -> RangeValue)
-> (LessThanD -> RangeValue)
-> (GreaterThanEqD -> RangeValue)
-> (LessThanEqD -> RangeValue)
-> Parser RangeValue
-> Object
-> Parser RangeValue
forall t4 t3 t2 t1 t5 t6 t7 t8 b.
(FromJSON t4, FromJSON t3, FromJSON t2, FromJSON t1) =>
(t3 -> t5)
-> (t1 -> t6)
-> (t4 -> t7)
-> (t2 -> t8)
-> (t5 -> t6 -> b)
-> (t7 -> t6 -> b)
-> (t5 -> t8 -> b)
-> (t7 -> t8 -> b)
-> (t5 -> b)
-> (t6 -> b)
-> (t7 -> b)
-> (t8 -> b)
-> Parser b
-> Object
-> Parser b
parseRangeValue
UTCTime -> GreaterThanD
GreaterThanD
UTCTime -> LessThanD
LessThanD
UTCTime -> GreaterThanEqD
GreaterThanEqD
UTCTime -> LessThanEqD
LessThanEqD
GreaterThanD -> LessThanD -> RangeValue
RangeDateGtLt
GreaterThanEqD -> LessThanD -> RangeValue
RangeDateGteLt
GreaterThanD -> LessThanEqD -> RangeValue
RangeDateGtLte
GreaterThanEqD -> LessThanEqD -> RangeValue
RangeDateGteLte
GreaterThanD -> RangeValue
RangeDateGt
LessThanD -> RangeValue
RangeDateLt
GreaterThanEqD -> RangeValue
RangeDateGte
LessThanEqD -> RangeValue
RangeDateLte
Parser RangeValue
forall a. Parser a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
Object
o
parseDouble :: Object -> Parser RangeValue
parseDouble Object
o =
(Double -> GreaterThan)
-> (Double -> LessThan)
-> (Double -> GreaterThanEq)
-> (Double -> LessThanEq)
-> (GreaterThan -> LessThan -> RangeValue)
-> (GreaterThanEq -> LessThan -> RangeValue)
-> (GreaterThan -> LessThanEq -> RangeValue)
-> (GreaterThanEq -> LessThanEq -> RangeValue)
-> (GreaterThan -> RangeValue)
-> (LessThan -> RangeValue)
-> (GreaterThanEq -> RangeValue)
-> (LessThanEq -> RangeValue)
-> Parser RangeValue
-> Object
-> Parser RangeValue
forall t4 t3 t2 t1 t5 t6 t7 t8 b.
(FromJSON t4, FromJSON t3, FromJSON t2, FromJSON t1) =>
(t3 -> t5)
-> (t1 -> t6)
-> (t4 -> t7)
-> (t2 -> t8)
-> (t5 -> t6 -> b)
-> (t7 -> t6 -> b)
-> (t5 -> t8 -> b)
-> (t7 -> t8 -> b)
-> (t5 -> b)
-> (t6 -> b)
-> (t7 -> b)
-> (t8 -> b)
-> Parser b
-> Object
-> Parser b
parseRangeValue
Double -> GreaterThan
GreaterThan
Double -> LessThan
LessThan
Double -> GreaterThanEq
GreaterThanEq
Double -> LessThanEq
LessThanEq
GreaterThan -> LessThan -> RangeValue
RangeDoubleGtLt
GreaterThanEq -> LessThan -> RangeValue
RangeDoubleGteLt
GreaterThan -> LessThanEq -> RangeValue
RangeDoubleGtLte
GreaterThanEq -> LessThanEq -> RangeValue
RangeDoubleGteLte
GreaterThan -> RangeValue
RangeDoubleGt
LessThan -> RangeValue
RangeDoubleLt
GreaterThanEq -> RangeValue
RangeDoubleGte
LessThanEq -> RangeValue
RangeDoubleLte
Parser RangeValue
forall a. Parser a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
Object
o
rangeValueToPair :: RangeValue -> [Pair]
rangeValueToPair :: RangeValue -> [Pair]
rangeValueToPair RangeValue
rv = case RangeValue
rv of
RangeDateLte (LessThanEqD UTCTime
t) -> [Key
"lte" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
t]
RangeDateGte (GreaterThanEqD UTCTime
t) -> [Key
"gte" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
t]
RangeDateLt (LessThanD UTCTime
t) -> [Key
"lt" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
t]
RangeDateGt (GreaterThanD UTCTime
t) -> [Key
"gt" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
t]
RangeDateGteLte (GreaterThanEqD UTCTime
l) (LessThanEqD UTCTime
g) -> [Key
"gte" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
l, Key
"lte" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
g]
RangeDateGtLte (GreaterThanD UTCTime
l) (LessThanEqD UTCTime
g) -> [Key
"gt" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
l, Key
"lte" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
g]
RangeDateGteLt (GreaterThanEqD UTCTime
l) (LessThanD UTCTime
g) -> [Key
"gte" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
l, Key
"lt" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
g]
RangeDateGtLt (GreaterThanD UTCTime
l) (LessThanD UTCTime
g) -> [Key
"gt" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
l, Key
"lt" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
g]
RangeDoubleLte (LessThanEq Double
t) -> [Key
"lte" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
t]
RangeDoubleGte (GreaterThanEq Double
t) -> [Key
"gte" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
t]
RangeDoubleLt (LessThan Double
t) -> [Key
"lt" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
t]
RangeDoubleGt (GreaterThan Double
t) -> [Key
"gt" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
t]
RangeDoubleGteLte (GreaterThanEq Double
l) (LessThanEq Double
g) -> [Key
"gte" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
l, Key
"lte" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
g]
RangeDoubleGtLte (GreaterThan Double
l) (LessThanEq Double
g) -> [Key
"gt" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
l, Key
"lte" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
g]
RangeDoubleGteLt (GreaterThanEq Double
l) (LessThan Double
g) -> [Key
"gte" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
l, Key
"lt" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
g]
RangeDoubleGtLt (GreaterThan Double
l) (LessThan Double
g) -> [Key
"gt" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
l, Key
"lt" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
g]