Safe Haskell | None |
---|---|
Language | Haskell2010 |
A query might specify a filter that should be applied to the results before returning them. This module implements a very limited subset of the specification: https://tools.ietf.org/html/rfc7644#section-3.4.2.2.
Supported:
- All comparison operators (
eq
,le
, etc) - The
userName
attribute
Not supported:
- The
pr
operator - Boolean operators
- Combined filters
- Fully qualified attribute names (schema prefixes, attribute paths)
Synopsis
- data Filter = FilterAttrCompare AttrPath CompareOp CompValue
- parseFilter :: [Schema] -> Text -> Either Text Filter
- renderFilter :: Filter -> Text
- data CompValue
- data CompareOp
- data AttrPath = AttrPath (Maybe Schema) AttrName (Maybe SubAttr)
- data ValuePath = ValuePath AttrPath Filter
- newtype SubAttr = SubAttr AttrName
- pAttrPath :: [Schema] -> Parser AttrPath
- pValuePath :: [Schema] -> Parser ValuePath
- pSubAttr :: Parser SubAttr
- pFilter :: [Schema] -> Parser Filter
- rAttrPath :: AttrPath -> Text
- rCompareOp :: CompareOp -> Text
- rValuePath :: ValuePath -> Text
- rSubAttr :: SubAttr -> Text
- compareStr :: CompareOp -> Text -> Text -> Bool
- topLevelAttrPath :: Text -> AttrPath
Filter type
A filter.
Our representation of filters is lax and doesn't attempt to ensure
validity on the type level. If a filter does something silly (e.g. tries
to compare a username with a boolean), it will be caught during filtering
and an appropriate error message will be thrown (see filterUser
).
TODO(arianvp): Implement the following grammar fully if we want to support more complex filters
FILTER = attrExp logExp valuePath / *1"not" "(" FILTER ")"
FilterAttrCompare AttrPath CompareOp CompValue | Compare the attribute value with a literal |
Instances
Eq Filter Source # | |
Show Filter Source # | |
ToHttpApiData Filter Source # | |
Defined in Web.Scim.Filter toUrlPiece :: Filter -> Text # toEncodedUrlPiece :: Filter -> Builder # toHeader :: Filter -> ByteString # toQueryParam :: Filter -> Text # | |
FromHttpApiData Filter Source # | We currently only support filtering on core user schema |
Defined in Web.Scim.Filter parseUrlPiece :: Text -> Either Text Filter # parseHeader :: ByteString -> Either Text Filter # |
parseFilter :: [Schema] -> Text -> Either Text Filter Source #
PATH = attrPath / valuePath [subAttr]
Currently we don't support matching on lists in paths as
we currently don't support filtering on arbitrary attributes yet
e.g.
"path":"members[value eq
"2819c223-7f76-453a-919d-413861904646"].displayName"
is not supported
Parse a filter. Spaces surrounding the filter will be stripped.
If parsing fails, returns a Left
with an error description.
Note: this parser is written with Attoparsec because I don't know how to lift an Attoparsec parser (from Aeson) to Megaparsec
renderFilter :: Filter -> Text Source #
Render a filter according to the SCIM spec.
Constructing filters
A value type. Attributes are compared against literal values.
A comparison operator.
OpEq | Equal |
OpNe | Not equal |
OpCo | Contains |
OpSw | Starts with |
OpEw | Ends with |
OpGt | Greater than |
OpGe | Greater than or equal to |
OpLt | Less than |
OpLe | Less than or equal to |
Instances
Bounded CompareOp Source # | |
Enum CompareOp Source # | |
Defined in Web.Scim.Filter succ :: CompareOp -> CompareOp # pred :: CompareOp -> CompareOp # fromEnum :: CompareOp -> Int # enumFrom :: CompareOp -> [CompareOp] # enumFromThen :: CompareOp -> CompareOp -> [CompareOp] # enumFromTo :: CompareOp -> CompareOp -> [CompareOp] # enumFromThenTo :: CompareOp -> CompareOp -> CompareOp -> [CompareOp] # | |
Eq CompareOp Source # | |
Ord CompareOp Source # | |
Defined in Web.Scim.Filter | |
Show CompareOp Source # | |
attrPath = [URI ":"] ATTRNAME *1subAtt
valuePath = attrPath "[" valFilter "]" TODO(arianvp): This is a slight simplification at the moment as we don't support the complete Filter grammar. This should be a valFilter, not a FILTER.
subAttr = "." ATTRNAME
pAttrPath :: [Schema] -> Parser AttrPath Source #
ATTRNAME = ALPHA *(nameChar) attrPath = [URI ":"] ATTRNAME *1subAtt
rCompareOp :: CompareOp -> Text Source #
Comparison operator renderer.
rValuePath :: ValuePath -> Text Source #
topLevelAttrPath :: Text -> AttrPath Source #
Smart constructor that refers to a toplevel field with default schema