{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Web.Scim.Filter
(
Filter (..),
parseFilter,
renderFilter,
CompValue (..),
CompareOp (..),
AttrPath (..),
ValuePath (..),
SubAttr (..),
pAttrPath,
pValuePath,
pSubAttr,
pFilter,
rAttrPath,
rCompareOp,
rValuePath,
rSubAttr,
compareStr,
topLevelAttrPath,
)
where
import Control.Applicative (optional)
import Data.Aeson as Aeson
import Data.Aeson.Parser as Aeson
import Data.Aeson.Text as Aeson
import Data.Attoparsec.ByteString.Char8
import Data.Scientific
import Data.String
import Data.Text (Text, isInfixOf, isPrefixOf, isSuffixOf, pack)
import Data.Text.Encoding (encodeUtf8)
import Data.Text.Lazy (toStrict)
import Lens.Micro
import Web.HttpApiData
import Web.Scim.AttrName
import Web.Scim.Schema.Schema (Schema (User20), getSchemaUri, pSchema)
import Prelude hiding (takeWhile)
data CompValue
= ValNull
| ValBool Bool
| ValNumber Scientific
| ValString Text
deriving (CompValue -> CompValue -> Bool
(CompValue -> CompValue -> Bool)
-> (CompValue -> CompValue -> Bool) -> Eq CompValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompValue -> CompValue -> Bool
== :: CompValue -> CompValue -> Bool
$c/= :: CompValue -> CompValue -> Bool
/= :: CompValue -> CompValue -> Bool
Eq, Eq CompValue
Eq CompValue =>
(CompValue -> CompValue -> Ordering)
-> (CompValue -> CompValue -> Bool)
-> (CompValue -> CompValue -> Bool)
-> (CompValue -> CompValue -> Bool)
-> (CompValue -> CompValue -> Bool)
-> (CompValue -> CompValue -> CompValue)
-> (CompValue -> CompValue -> CompValue)
-> Ord CompValue
CompValue -> CompValue -> Bool
CompValue -> CompValue -> Ordering
CompValue -> CompValue -> CompValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CompValue -> CompValue -> Ordering
compare :: CompValue -> CompValue -> Ordering
$c< :: CompValue -> CompValue -> Bool
< :: CompValue -> CompValue -> Bool
$c<= :: CompValue -> CompValue -> Bool
<= :: CompValue -> CompValue -> Bool
$c> :: CompValue -> CompValue -> Bool
> :: CompValue -> CompValue -> Bool
$c>= :: CompValue -> CompValue -> Bool
>= :: CompValue -> CompValue -> Bool
$cmax :: CompValue -> CompValue -> CompValue
max :: CompValue -> CompValue -> CompValue
$cmin :: CompValue -> CompValue -> CompValue
min :: CompValue -> CompValue -> CompValue
Ord, Int -> CompValue -> ShowS
[CompValue] -> ShowS
CompValue -> String
(Int -> CompValue -> ShowS)
-> (CompValue -> String)
-> ([CompValue] -> ShowS)
-> Show CompValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompValue -> ShowS
showsPrec :: Int -> CompValue -> ShowS
$cshow :: CompValue -> String
show :: CompValue -> String
$cshowList :: [CompValue] -> ShowS
showList :: [CompValue] -> ShowS
Show)
data CompareOp
=
OpEq
|
OpNe
|
OpCo
|
OpSw
|
OpEw
|
OpGt
|
OpGe
|
OpLt
|
OpLe
deriving (CompareOp -> CompareOp -> Bool
(CompareOp -> CompareOp -> Bool)
-> (CompareOp -> CompareOp -> Bool) -> Eq CompareOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompareOp -> CompareOp -> Bool
== :: CompareOp -> CompareOp -> Bool
$c/= :: CompareOp -> CompareOp -> Bool
/= :: CompareOp -> CompareOp -> Bool
Eq, Eq CompareOp
Eq CompareOp =>
(CompareOp -> CompareOp -> Ordering)
-> (CompareOp -> CompareOp -> Bool)
-> (CompareOp -> CompareOp -> Bool)
-> (CompareOp -> CompareOp -> Bool)
-> (CompareOp -> CompareOp -> Bool)
-> (CompareOp -> CompareOp -> CompareOp)
-> (CompareOp -> CompareOp -> CompareOp)
-> Ord CompareOp
CompareOp -> CompareOp -> Bool
CompareOp -> CompareOp -> Ordering
CompareOp -> CompareOp -> CompareOp
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CompareOp -> CompareOp -> Ordering
compare :: CompareOp -> CompareOp -> Ordering
$c< :: CompareOp -> CompareOp -> Bool
< :: CompareOp -> CompareOp -> Bool
$c<= :: CompareOp -> CompareOp -> Bool
<= :: CompareOp -> CompareOp -> Bool
$c> :: CompareOp -> CompareOp -> Bool
> :: CompareOp -> CompareOp -> Bool
$c>= :: CompareOp -> CompareOp -> Bool
>= :: CompareOp -> CompareOp -> Bool
$cmax :: CompareOp -> CompareOp -> CompareOp
max :: CompareOp -> CompareOp -> CompareOp
$cmin :: CompareOp -> CompareOp -> CompareOp
min :: CompareOp -> CompareOp -> CompareOp
Ord, Int -> CompareOp -> ShowS
[CompareOp] -> ShowS
CompareOp -> String
(Int -> CompareOp -> ShowS)
-> (CompareOp -> String)
-> ([CompareOp] -> ShowS)
-> Show CompareOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompareOp -> ShowS
showsPrec :: Int -> CompareOp -> ShowS
$cshow :: CompareOp -> String
show :: CompareOp -> String
$cshowList :: [CompareOp] -> ShowS
showList :: [CompareOp] -> ShowS
Show, Int -> CompareOp
CompareOp -> Int
CompareOp -> [CompareOp]
CompareOp -> CompareOp
CompareOp -> CompareOp -> [CompareOp]
CompareOp -> CompareOp -> CompareOp -> [CompareOp]
(CompareOp -> CompareOp)
-> (CompareOp -> CompareOp)
-> (Int -> CompareOp)
-> (CompareOp -> Int)
-> (CompareOp -> [CompareOp])
-> (CompareOp -> CompareOp -> [CompareOp])
-> (CompareOp -> CompareOp -> [CompareOp])
-> (CompareOp -> CompareOp -> CompareOp -> [CompareOp])
-> Enum CompareOp
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: CompareOp -> CompareOp
succ :: CompareOp -> CompareOp
$cpred :: CompareOp -> CompareOp
pred :: CompareOp -> CompareOp
$ctoEnum :: Int -> CompareOp
toEnum :: Int -> CompareOp
$cfromEnum :: CompareOp -> Int
fromEnum :: CompareOp -> Int
$cenumFrom :: CompareOp -> [CompareOp]
enumFrom :: CompareOp -> [CompareOp]
$cenumFromThen :: CompareOp -> CompareOp -> [CompareOp]
enumFromThen :: CompareOp -> CompareOp -> [CompareOp]
$cenumFromTo :: CompareOp -> CompareOp -> [CompareOp]
enumFromTo :: CompareOp -> CompareOp -> [CompareOp]
$cenumFromThenTo :: CompareOp -> CompareOp -> CompareOp -> [CompareOp]
enumFromThenTo :: CompareOp -> CompareOp -> CompareOp -> [CompareOp]
Enum, CompareOp
CompareOp -> CompareOp -> Bounded CompareOp
forall a. a -> a -> Bounded a
$cminBound :: CompareOp
minBound :: CompareOp
$cmaxBound :: CompareOp
maxBound :: CompareOp
Bounded)
data Filter
=
FilterAttrCompare AttrPath CompareOp CompValue
deriving (Filter -> Filter -> Bool
(Filter -> Filter -> Bool)
-> (Filter -> Filter -> Bool) -> Eq Filter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Filter -> Filter -> Bool
== :: Filter -> Filter -> Bool
$c/= :: Filter -> Filter -> Bool
/= :: Filter -> Filter -> Bool
Eq, Int -> Filter -> ShowS
[Filter] -> ShowS
Filter -> String
(Int -> Filter -> ShowS)
-> (Filter -> String) -> ([Filter] -> ShowS) -> Show Filter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Filter -> ShowS
showsPrec :: Int -> Filter -> ShowS
$cshow :: Filter -> String
show :: Filter -> String
$cshowList :: [Filter] -> ShowS
showList :: [Filter] -> ShowS
Show)
data ValuePath = ValuePath AttrPath Filter
deriving (ValuePath -> ValuePath -> Bool
(ValuePath -> ValuePath -> Bool)
-> (ValuePath -> ValuePath -> Bool) -> Eq ValuePath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValuePath -> ValuePath -> Bool
== :: ValuePath -> ValuePath -> Bool
$c/= :: ValuePath -> ValuePath -> Bool
/= :: ValuePath -> ValuePath -> Bool
Eq, Int -> ValuePath -> ShowS
[ValuePath] -> ShowS
ValuePath -> String
(Int -> ValuePath -> ShowS)
-> (ValuePath -> String)
-> ([ValuePath] -> ShowS)
-> Show ValuePath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValuePath -> ShowS
showsPrec :: Int -> ValuePath -> ShowS
$cshow :: ValuePath -> String
show :: ValuePath -> String
$cshowList :: [ValuePath] -> ShowS
showList :: [ValuePath] -> ShowS
Show)
newtype SubAttr = SubAttr AttrName
deriving (SubAttr -> SubAttr -> Bool
(SubAttr -> SubAttr -> Bool)
-> (SubAttr -> SubAttr -> Bool) -> Eq SubAttr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubAttr -> SubAttr -> Bool
== :: SubAttr -> SubAttr -> Bool
$c/= :: SubAttr -> SubAttr -> Bool
/= :: SubAttr -> SubAttr -> Bool
Eq, Int -> SubAttr -> ShowS
[SubAttr] -> ShowS
SubAttr -> String
(Int -> SubAttr -> ShowS)
-> (SubAttr -> String) -> ([SubAttr] -> ShowS) -> Show SubAttr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubAttr -> ShowS
showsPrec :: Int -> SubAttr -> ShowS
$cshow :: SubAttr -> String
show :: SubAttr -> String
$cshowList :: [SubAttr] -> ShowS
showList :: [SubAttr] -> ShowS
Show, String -> SubAttr
(String -> SubAttr) -> IsString SubAttr
forall a. (String -> a) -> IsString a
$cfromString :: String -> SubAttr
fromString :: String -> SubAttr
IsString)
data AttrPath = AttrPath (Maybe Schema) AttrName (Maybe SubAttr)
deriving (AttrPath -> AttrPath -> Bool
(AttrPath -> AttrPath -> Bool)
-> (AttrPath -> AttrPath -> Bool) -> Eq AttrPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttrPath -> AttrPath -> Bool
== :: AttrPath -> AttrPath -> Bool
$c/= :: AttrPath -> AttrPath -> Bool
/= :: AttrPath -> AttrPath -> Bool
Eq, Int -> AttrPath -> ShowS
[AttrPath] -> ShowS
AttrPath -> String
(Int -> AttrPath -> ShowS)
-> (AttrPath -> String) -> ([AttrPath] -> ShowS) -> Show AttrPath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AttrPath -> ShowS
showsPrec :: Int -> AttrPath -> ShowS
$cshow :: AttrPath -> String
show :: AttrPath -> String
$cshowList :: [AttrPath] -> ShowS
showList :: [AttrPath] -> ShowS
Show)
topLevelAttrPath :: Text -> AttrPath
topLevelAttrPath :: Text -> AttrPath
topLevelAttrPath Text
x = Maybe Schema -> AttrName -> Maybe SubAttr -> AttrPath
AttrPath Maybe Schema
forall a. Maybe a
Nothing (Text -> AttrName
AttrName Text
x) Maybe SubAttr
forall a. Maybe a
Nothing
parseFilter :: [Schema] -> Text -> Either Text Filter
parseFilter :: [Schema] -> Text -> Either Text Filter
parseFilter [Schema]
supportedSchemas =
ASetter (Either String Filter) (Either Text Filter) String Text
-> (String -> Text) -> Either String Filter -> Either Text Filter
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter (Either String Filter) (Either Text Filter) String Text
forall a b a' (f :: * -> *).
Applicative f =>
(a -> f a') -> Either a b -> f (Either a' b)
_Left String -> Text
pack
(Either String Filter -> Either Text Filter)
-> (Text -> Either String Filter) -> Text -> Either Text Filter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser Filter -> ByteString -> Either String Filter
forall a. Parser a -> ByteString -> Either String a
parseOnly (Parser ()
skipSpace Parser () -> Parser Filter -> Parser Filter
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [Schema] -> Parser Filter
pFilter [Schema]
supportedSchemas Parser Filter -> Parser () -> Parser Filter
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
skipSpace Parser Filter -> Parser () -> Parser Filter
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
forall t. Chunk t => Parser t ()
endOfInput)
(ByteString -> Either String Filter)
-> (Text -> ByteString) -> Text -> Either String Filter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8
pAttrPath :: [Schema] -> Parser AttrPath
pAttrPath :: [Schema] -> Parser AttrPath
pAttrPath [Schema]
supportedSchemas = do
Maybe Schema
schema <- Parser ByteString Schema -> Parser ByteString (Maybe Schema)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ([Schema] -> Parser ByteString Schema
pSchema [Schema]
supportedSchemas Parser ByteString Schema
-> Parser ByteString Char -> Parser ByteString Schema
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser ByteString Char
char Char
':')
Maybe Schema -> AttrName -> Maybe SubAttr -> AttrPath
AttrPath Maybe Schema
schema (AttrName -> Maybe SubAttr -> AttrPath)
-> Parser ByteString AttrName
-> Parser ByteString (Maybe SubAttr -> AttrPath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString AttrName
pAttrName Parser ByteString (Maybe SubAttr -> AttrPath)
-> Parser ByteString (Maybe SubAttr) -> Parser AttrPath
forall a b.
Parser ByteString (a -> b)
-> Parser ByteString a -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser ByteString SubAttr -> Parser ByteString (Maybe SubAttr)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser ByteString SubAttr
pSubAttr
pSubAttr :: Parser SubAttr
pSubAttr :: Parser ByteString SubAttr
pSubAttr = Char -> Parser ByteString Char
char Char
'.' Parser ByteString Char
-> Parser ByteString SubAttr -> Parser ByteString SubAttr
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (AttrName -> SubAttr
SubAttr (AttrName -> SubAttr)
-> Parser ByteString AttrName -> Parser ByteString SubAttr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString AttrName
pAttrName)
pValuePath :: [Schema] -> Parser ValuePath
pValuePath :: [Schema] -> Parser ValuePath
pValuePath [Schema]
supportedSchemas =
AttrPath -> Filter -> ValuePath
ValuePath (AttrPath -> Filter -> ValuePath)
-> Parser AttrPath -> Parser ByteString (Filter -> ValuePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Schema] -> Parser AttrPath
pAttrPath [Schema]
supportedSchemas Parser ByteString (Filter -> ValuePath)
-> Parser Filter -> Parser ValuePath
forall a b.
Parser ByteString (a -> b)
-> Parser ByteString a -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Char -> Parser ByteString Char
char Char
'[' Parser ByteString Char -> Parser Filter -> Parser Filter
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [Schema] -> Parser Filter
pFilter [Schema]
supportedSchemas Parser Filter -> Parser ByteString Char -> Parser Filter
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser ByteString Char
char Char
']')
pCompValue :: Parser CompValue
pCompValue :: Parser CompValue
pCompValue =
[Parser CompValue] -> Parser CompValue
forall (f :: * -> *) a. Alternative f => [f a] -> f a
choice
[ CompValue
ValNull CompValue -> Parser ByteString ByteString -> Parser CompValue
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
string ByteString
"null",
Bool -> CompValue
ValBool Bool
True CompValue -> Parser ByteString ByteString -> Parser CompValue
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"true",
Bool -> CompValue
ValBool Bool
False CompValue -> Parser ByteString ByteString -> Parser CompValue
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"false",
Scientific -> CompValue
ValNumber (Scientific -> CompValue)
-> Parser ByteString Scientific -> Parser CompValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString Scientific
Aeson.scientific,
Text -> CompValue
ValString (Text -> CompValue) -> Parser ByteString Text -> Parser CompValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString Text
Aeson.jstring
]
pCompareOp :: Parser CompareOp
pCompareOp :: Parser CompareOp
pCompareOp =
[Parser CompareOp] -> Parser CompareOp
forall (f :: * -> *) a. Alternative f => [f a] -> f a
choice
[ CompareOp
OpEq CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"eq",
CompareOp
OpNe CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"ne",
CompareOp
OpCo CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"co",
CompareOp
OpSw CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"sw",
CompareOp
OpEw CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"ew",
CompareOp
OpGt CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"gt",
CompareOp
OpGe CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"ge",
CompareOp
OpLt CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"lt",
CompareOp
OpLe CompareOp -> Parser ByteString ByteString -> Parser CompareOp
forall a b. a -> Parser ByteString b -> Parser ByteString a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> Parser ByteString ByteString
stringCI ByteString
"le"
]
pFilter :: [Schema] -> Parser Filter
pFilter :: [Schema] -> Parser Filter
pFilter [Schema]
supportedSchemas =
AttrPath -> CompareOp -> CompValue -> Filter
FilterAttrCompare
(AttrPath -> CompareOp -> CompValue -> Filter)
-> Parser AttrPath
-> Parser ByteString (CompareOp -> CompValue -> Filter)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Schema] -> Parser AttrPath
pAttrPath [Schema]
supportedSchemas
Parser ByteString (CompareOp -> CompValue -> Filter)
-> Parser CompareOp -> Parser ByteString (CompValue -> Filter)
forall a b.
Parser ByteString (a -> b)
-> Parser ByteString a -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser ()
skipSpace1 Parser () -> Parser CompareOp -> Parser CompareOp
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser CompareOp
pCompareOp)
Parser ByteString (CompValue -> Filter)
-> Parser CompValue -> Parser Filter
forall a b.
Parser ByteString (a -> b)
-> Parser ByteString a -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser ()
skipSpace1 Parser () -> Parser CompValue -> Parser CompValue
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser CompValue
pCompValue)
skipSpace1 :: Parser ()
skipSpace1 :: Parser ()
skipSpace1 = Parser ByteString Char
space Parser ByteString Char -> Parser () -> Parser ()
forall a b.
Parser ByteString a -> Parser ByteString b -> Parser ByteString b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser ()
skipSpace
renderFilter :: Filter -> Text
renderFilter :: Filter -> Text
renderFilter Filter
filter_ = case Filter
filter_ of
FilterAttrCompare AttrPath
attr CompareOp
op CompValue
val ->
AttrPath -> Text
rAttrPath AttrPath
attr Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> CompareOp -> Text
rCompareOp CompareOp
op Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> CompValue -> Text
rCompValue CompValue
val
rAttrPath :: AttrPath -> Text
rAttrPath :: AttrPath -> Text
rAttrPath (AttrPath Maybe Schema
schema AttrName
attr Maybe SubAttr
subAttr) =
Text -> (Schema -> Text) -> Maybe Schema -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" ((Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":") (Text -> Text) -> (Schema -> Text) -> Schema -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Text
getSchemaUri) Maybe Schema
schema
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> AttrName -> Text
rAttrName AttrName
attr
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> (SubAttr -> Text) -> Maybe SubAttr -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" SubAttr -> Text
rSubAttr Maybe SubAttr
subAttr
rSubAttr :: SubAttr -> Text
rSubAttr :: SubAttr -> Text
rSubAttr (SubAttr AttrName
x) = Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> AttrName -> Text
rAttrName AttrName
x
rValuePath :: ValuePath -> Text
rValuePath :: ValuePath -> Text
rValuePath (ValuePath AttrPath
attrPath Filter
filter') = AttrPath -> Text
rAttrPath AttrPath
attrPath Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Filter -> Text
renderFilter Filter
filter' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
rCompValue :: CompValue -> Text
rCompValue :: CompValue -> Text
rCompValue = \case
CompValue
ValNull -> Text
"null"
ValBool Bool
True -> Text
"true"
ValBool Bool
False -> Text
"false"
ValNumber Scientific
n -> Text -> Text
toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Text
forall a. ToJSON a => a -> Text
Aeson.encodeToLazyText (Scientific -> Value
Aeson.Number Scientific
n)
ValString Text
s -> Text -> Text
toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Text
forall a. ToJSON a => a -> Text
Aeson.encodeToLazyText (Text -> Value
Aeson.String Text
s)
rCompareOp :: CompareOp -> Text
rCompareOp :: CompareOp -> Text
rCompareOp = \case
CompareOp
OpEq -> Text
"eq"
CompareOp
OpNe -> Text
"ne"
CompareOp
OpCo -> Text
"co"
CompareOp
OpSw -> Text
"sw"
CompareOp
OpEw -> Text
"ew"
CompareOp
OpGt -> Text
"gt"
CompareOp
OpGe -> Text
"ge"
CompareOp
OpLt -> Text
"lt"
CompareOp
OpLe -> Text
"le"
compareStr :: CompareOp -> Text -> Text -> Bool
compareStr :: CompareOp -> Text -> Text -> Bool
compareStr = \case
CompareOp
OpEq -> Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(==)
CompareOp
OpNe -> Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(/=)
CompareOp
OpCo -> (Text -> Text -> Bool) -> Text -> Text -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Text -> Bool
isInfixOf
CompareOp
OpSw -> (Text -> Text -> Bool) -> Text -> Text -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Text -> Bool
isPrefixOf
CompareOp
OpEw -> (Text -> Text -> Bool) -> Text -> Text -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Text -> Bool
isSuffixOf
CompareOp
OpGt -> Text -> Text -> Bool
forall a. Ord a => a -> a -> Bool
(>)
CompareOp
OpGe -> Text -> Text -> Bool
forall a. Ord a => a -> a -> Bool
(>=)
CompareOp
OpLt -> Text -> Text -> Bool
forall a. Ord a => a -> a -> Bool
(<)
CompareOp
OpLe -> Text -> Text -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
instance FromHttpApiData Filter where
parseUrlPiece :: Text -> Either Text Filter
parseUrlPiece = [Schema] -> Text -> Either Text Filter
parseFilter [Schema
User20]
instance ToHttpApiData Filter where
toUrlPiece :: Filter -> Text
toUrlPiece = Filter -> Text
renderFilter