{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
module Web.Scim.Test.Acceptance
( module Web.Scim.Test.Acceptance,
module Web.Scim.Test.Util,
)
where
import Control.Monad.IO.Class (liftIO)
import qualified Data.Aeson as Aeson
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as L
import Data.String.Conversions (cs)
import Data.Text (Text)
import Network.HTTP.Types.Status
import Network.Wai.Test
import Servant.API as Servant
import Test.Hspec (Spec, beforeAll, describe, it, pending, pendingWith, shouldBe, shouldSatisfy)
import Test.Hspec.Wai (matchStatus)
import Test.Hspec.Wai.Internal (runWaiSession)
import Web.Scim.Class.User
import Web.Scim.Schema.Common as Hscim
import qualified Web.Scim.Schema.ListResponse as ListResponse
import Web.Scim.Schema.Meta
import Web.Scim.Schema.UserTypes
import Web.Scim.Test.Util
ignore :: Monad m => m a -> m ()
ignore :: m a -> m ()
ignore m a
_ = () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
microsoftAzure :: forall tag. (Aeson.FromJSON (UserId tag), Aeson.FromJSON (UserExtra tag), ToHttpApiData (UserId tag)) => AcceptanceConfig tag -> Spec
microsoftAzure :: AcceptanceConfig tag -> Spec
microsoftAzure AcceptanceConfig {Bool
IO (Application, AcceptanceQueryConfig tag)
IO Text
responsesFullyKnown :: forall tag. AcceptanceConfig tag -> Bool
genUserName :: forall tag. AcceptanceConfig tag -> IO Text
scimAppAndConfig :: forall tag.
AcceptanceConfig tag -> IO (Application, AcceptanceQueryConfig tag)
responsesFullyKnown :: Bool
genUserName :: IO Text
scimAppAndConfig :: IO (Application, AcceptanceQueryConfig tag)
..} = do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Within the SCIM 2.0 protocol specification, your application must meet these requirements:" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Supports creating users, and optionally also groups, as per section 3.3 of the SCIM protocol." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Supports modifying users or groups with PATCH requests, as per section 3.5.2 of the SCIM protocol." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Supports retrieving a known resource for a user or group created earlier, as per section 3.4.1 of the SCIM protocol." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Supports querying users or groups, as per section 3.4.2 of the SCIM protocol. By default, users are retrieved by their id and queried by their username and externalid, and groups are queried by displayName." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Supports querying user by ID and by manager, as per section 3.4.2 of the SCIM protocol." (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"query by id" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"query by manager" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Supports querying groups by ID and by member, as per section 3.4.2 of the SCIM protocol." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Accepts a single bearer token for authentication and authorization of Azure AD to your application." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
Bool
True Bool -> Bool -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Bool
True
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Follow these general guidelines when implementing a SCIM endpoint to ensure compatibility with Azure AD:" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"id is a required property for all the resources. Every response that returns a resource should ensure each resource has this property, except for ListResponse with zero members." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
Bool
True Bool -> Bool -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Bool
True
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Response to a query/filter request should always be a ListResponse." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
Bool
True Bool -> Bool -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Bool
True
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Groups are optional, but only supported if the SCIM implementation supports PATCH requests." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
Bool
True Bool -> Bool -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Bool
True
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Don't require a case-sensitive match on structural elements in SCIM, in particular PATCH op operation values, as defined in https://tools.ietf.org/html/rfc7644#section-3.5.2. Azure AD emits the values of 'op' as Add, " (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
Expectation
HasCallStack => Expectation
pending
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Microsoft Azure AD only uses the following operators: eq and" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"eq" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"and" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ Expectation
HasCallStack => Expectation
pending
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"good errors" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"surfaces parse errors of the user id path segment" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
HasCallStack => String -> Expectation
String -> Expectation
pendingWith String
"should contain the offending id and the error; currently contains neither"
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"same for user id in query" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
Expectation
HasCallStack => Expectation
pending
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"same for all other things parsed in path, query, body, ..." (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
Expectation
HasCallStack => Expectation
pending
IO (Application, AcceptanceQueryConfig tag)
-> SpecWith (Application, AcceptanceQueryConfig tag) -> Spec
forall a. IO a -> SpecWith a -> Spec
beforeAll IO (Application, AcceptanceQueryConfig tag)
scimAppAndConfig (SpecWith (Application, AcceptanceQueryConfig tag) -> Spec)
-> SpecWith (Application, AcceptanceQueryConfig tag) -> Spec
forall a b. (a -> b) -> a -> b
$ do
String
-> ((Application, AcceptanceQueryConfig tag) -> Expectation)
-> SpecWith
(Arg ((Application, AcceptanceQueryConfig tag) -> Expectation))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"User Operations" (((Application, AcceptanceQueryConfig tag) -> Expectation)
-> SpecWith
(Arg ((Application, AcceptanceQueryConfig tag) -> Expectation)))
-> ((Application, AcceptanceQueryConfig tag) -> Expectation)
-> SpecWith
(Arg ((Application, AcceptanceQueryConfig tag) -> Expectation))
forall a b. (a -> b) -> a -> b
$ \(Application
app, AcceptanceQueryConfig tag
queryConfig) -> (WaiSession () -> Application -> Expectation)
-> Application -> WaiSession () -> Expectation
forall a b c. (a -> b -> c) -> b -> a -> c
flip WaiSession () -> Application -> Expectation
forall a. WaiSession a -> Application -> IO a
runWaiSession Application
app (WaiSession () -> Expectation) -> WaiSession () -> Expectation
forall a b. (a -> b) -> a -> b
$ do
Text
userName1 <- IO Text -> WaiSession Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Text
genUserName
Text
userName2 <- IO Text -> WaiSession Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Text
genUserName
SResponse
resp :: SResponse <- AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
post' AcceptanceQueryConfig tag
queryConfig ByteString
"/Users" (Text -> ByteString
sampleUser1 Text
userName1)
Expectation -> WaiSession ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Expectation -> WaiSession ()) -> Expectation -> WaiSession ()
forall a b. (a -> b) -> a -> b
$ SResponse -> Status
simpleStatus SResponse
resp Status -> Status -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Status
status201
let testuid :: BS.ByteString
testuid :: ByteString
testuid =
(String -> ByteString)
-> (WithMeta (WithId (UserId tag) (User tag)) -> ByteString)
-> Either String (WithMeta (WithId (UserId tag) (User tag)))
-> ByteString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> ByteString
forall a. HasCallStack => String -> a
error (String -> ByteString)
-> (String -> String) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, SResponse) -> String
forall a. Show a => a -> String
show ((String, SResponse) -> String)
-> (String -> (String, SResponse)) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,SResponse
resp)) (Text -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs (Text -> ByteString)
-> (WithMeta (WithId (UserId tag) (User tag)) -> Text)
-> WithMeta (WithId (UserId tag) (User tag))
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserId tag -> Text
forall a. ToHttpApiData a => a -> Text
Servant.toUrlPiece (UserId tag -> Text)
-> (WithMeta (WithId (UserId tag) (User tag)) -> UserId tag)
-> WithMeta (WithId (UserId tag) (User tag))
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WithId (UserId tag) (User tag) -> UserId tag
forall id a. WithId id a -> id
Hscim.id (WithId (UserId tag) (User tag) -> UserId tag)
-> (WithMeta (WithId (UserId tag) (User tag))
-> WithId (UserId tag) (User tag))
-> WithMeta (WithId (UserId tag) (User tag))
-> UserId tag
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WithMeta (WithId (UserId tag) (User tag))
-> WithId (UserId tag) (User tag)
forall a. WithMeta a -> a
thing) (Either String (WithMeta (WithId (UserId tag) (User tag)))
-> ByteString)
-> Either String (WithMeta (WithId (UserId tag) (User tag)))
-> ByteString
forall a b. (a -> b) -> a -> b
$
ByteString
-> Either String (WithMeta (WithId (UserId tag) (User tag)))
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecode' @(StoredUser tag) (SResponse -> ByteString
simpleBody SResponse
resp)
AcceptanceQueryConfig tag -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag -> ByteString -> WaiSession SResponse
get' AcceptanceQueryConfig tag
queryConfig ByteString
"/Users" WaiSession SResponse
-> (SResponse -> WaiSession ()) -> WaiSession ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SResponse
rsp -> Expectation -> WaiSession ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Expectation -> WaiSession ()) -> Expectation -> WaiSession ()
forall a b. (a -> b) -> a -> b
$ do
SResponse -> Status
simpleStatus SResponse
rsp Status -> (Status -> Bool) -> Expectation
forall a. (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation
`shouldSatisfy` (Status -> [Status] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Status
status200, Status
status400])
AcceptanceQueryConfig tag -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag -> ByteString -> WaiSession SResponse
get' AcceptanceQueryConfig tag
queryConfig (String -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ String
"/Users?filter=userName eq " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
userName1) WaiSession SResponse
-> (SResponse -> WaiSession ()) -> WaiSession ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SResponse
rsp -> Expectation -> WaiSession ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Expectation -> WaiSession ()) -> Expectation -> WaiSession ()
forall a b. (a -> b) -> a -> b
$ do
SResponse -> Status
simpleStatus SResponse
rsp Status -> Status -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Status
status200
ListResponse (WithMeta (WithId (UserId tag) (User tag))) -> Int
forall a. ListResponse a -> Int
ListResponse.totalResults (ListResponse (WithMeta (WithId (UserId tag) (User tag))) -> Int)
-> Either
String (ListResponse (WithMeta (WithId (UserId tag) (User tag))))
-> Either String Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> Either
String (ListResponse (WithMeta (WithId (UserId tag) (User tag))))
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecode' @(ListResponse.ListResponse (StoredUser tag)) (SResponse -> ByteString
simpleBody SResponse
rsp) Either String Int -> Either String Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int -> Either String Int
forall a b. b -> Either a b
Right Int
1
AcceptanceQueryConfig tag -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag -> ByteString -> WaiSession SResponse
get' AcceptanceQueryConfig tag
queryConfig (String -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ String
"/Users?filter=userName eq " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
userName2)
HasCallStack =>
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
`shouldRespondWith` [scim|
{
"schemas": ["urn:ietf:params:scim:api:messages:2.0:ListResponse"],
"totalResults": 0,
"Resources": [],
"startIndex": 1,
"itemsPerPage": 0
}
|]
{ matchStatus :: Int
matchStatus = Int
200
}
WaiSession () -> WaiSession ()
forall (m :: * -> *) a. Monad m => m a -> m ()
ignore (WaiSession () -> WaiSession ()) -> WaiSession () -> WaiSession ()
forall a b. (a -> b) -> a -> b
$ do
AcceptanceQueryConfig tag -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag -> ByteString -> WaiSession SResponse
get' AcceptanceQueryConfig tag
queryConfig ByteString
"/Users?filter=externalId eq \"0a21f0f2-8d2a-4f8e-479e-a20b-2d77186b5dd1\"" WaiSession SResponse
-> (SResponse -> WaiSession ()) -> WaiSession ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SResponse
rsp -> Expectation -> WaiSession ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Expectation -> WaiSession ()) -> Expectation -> WaiSession ()
forall a b. (a -> b) -> a -> b
$ do
SResponse -> Status
simpleStatus SResponse
rsp Status -> Status -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Status
status200
ListResponse (WithMeta (WithId (UserId tag) (User tag))) -> Int
forall a. ListResponse a -> Int
ListResponse.totalResults (ListResponse (WithMeta (WithId (UserId tag) (User tag))) -> Int)
-> Either
String (ListResponse (WithMeta (WithId (UserId tag) (User tag))))
-> Either String Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> Either
String (ListResponse (WithMeta (WithId (UserId tag) (User tag))))
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecode' @(ListResponse.ListResponse (StoredUser tag)) (SResponse -> ByteString
simpleBody SResponse
rsp) Either String Int -> Either String Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int -> Either String Int
forall a b. b -> Either a b
Right Int
1
WaiSession () -> WaiSession ()
forall (m :: * -> *) a. Monad m => m a -> m ()
ignore (WaiSession () -> WaiSession ()) -> WaiSession () -> WaiSession ()
forall a b. (a -> b) -> a -> b
$
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
patch'
AcceptanceQueryConfig tag
queryConfig
ByteString
"/Users/0"
[scim|
{
"schemas": ["urn:ietf:params:scim:api:messages:2.0:PatchOp"],
"Operations": [
{
"op": "Replace",
"path": "emails[type eq \"work\"].value",
"value": "updatedEmail@microsoft.com"
},
{
"op": "Replace",
"path": "name.familyName",
"value": "updatedFamilyName"
}
]
}
|]
HasCallStack =>
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
`shouldRespondWith` ResponseMatcher
200
let ops1 :: ByteString
ops1 =
[scim|
{
"schemas": ["urn:ietf:params:scim:api:messages:2.0:PatchOp"],
"Operations": [{
"op": "Replace",
"path": "userName",
"value": #{userName2}
}]
}
|]
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
patch' AcceptanceQueryConfig tag
queryConfig (ByteString
"/Users/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
testuid) ByteString
ops1 HasCallStack =>
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
`shouldRespondWith` ResponseMatcher
200
let ops2 :: ByteString
ops2 =
[scim|
{
"schemas": ["urn:ietf:params:scim:api:messages:2.0:PatchOp"],
"Operations": [{
"op": "Replace",
"path": "displayName",
"value": "newDisplayName"
}]
}
|]
exactResult :: ResponseMatcher
exactResult =
[scim|
{
"schemas": [
"urn:ietf:params:scim:schemas:core:2.0:User",
"urn:ietf:params:scim:schemas:extension:enterprise:2.0:User"
],
"userName": #{userName2},
"active": true,
"name": {
"givenName": "givenName",
"formatted": "givenName familyName",
"familyName": "familyName"
},
"emails": [
{
"value": #{userName1 <> "@testuser.com"},
"primary": true,
"type": "work"
}
],
"displayName": "newDisplayName",
"id": "0",
"meta": {
"resourceType": "User",
"location": "https://example.com/Users/id",
"created": "2018-01-01T00:00:00Z",
"version": "W/\"testVersion\"",
"lastModified": "2018-01-01T00:00:00Z"
},
"externalId": "0a21f0f2-8d2a-4f8e-bf98-7363c4aed4ef"
}
|]
result :: ResponseMatcher
result =
if Bool
responsesFullyKnown
then ResponseMatcher
exactResult
else ResponseMatcher
200
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
patch' AcceptanceQueryConfig tag
queryConfig (ByteString
"/Users/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
testuid) ByteString
ops2 HasCallStack =>
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
`shouldRespondWith` ResponseMatcher
result
let op3 :: ByteString
op3 =
[scim|
{
"schemas": ["urn:ietf:params:scim:api:messages:2.0:PatchOp"],
"Operations": [{
"op": "Remove",
"path": "displayName"
}]
}
|]
exactResult3 :: ResponseMatcher
exactResult3 =
[scim|
{
"schemas": [
"urn:ietf:params:scim:schemas:core:2.0:User",
"urn:ietf:params:scim:schemas:extension:enterprise:2.0:User"
],
"userName": #{userName2},
"active": true,
"name": {
"givenName": "givenName",
"formatted": "givenName familyName",
"familyName": "familyName"
},
"emails": [
{
"value": #{userName1 <> "@testuser.com"},
"primary": true,
"type": "work"
}
],
"id": "0",
"meta": {
"resourceType": "User",
"location": "https://example.com/Users/id",
"created": "2018-01-01T00:00:00Z",
"version": "W/\"testVersion\"",
"lastModified": "2018-01-01T00:00:00Z"
},
"externalId": "0a21f0f2-8d2a-4f8e-bf98-7363c4aed4ef"
}
|]
result3 :: ResponseMatcher
result3 =
if Bool
responsesFullyKnown
then ResponseMatcher
exactResult3
else ResponseMatcher
200
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
patch' AcceptanceQueryConfig tag
queryConfig (ByteString
"/Users/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
testuid) ByteString
op3 HasCallStack =>
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
`shouldRespondWith` ResponseMatcher
result3
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
delete' AcceptanceQueryConfig tag
queryConfig (ByteString
"/Users/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
testuid) ByteString
"" HasCallStack =>
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
`shouldRespondWith` ResponseMatcher
204
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
forall tag.
AcceptanceQueryConfig tag
-> ByteString -> ByteString -> WaiSession SResponse
delete' AcceptanceQueryConfig tag
queryConfig (ByteString
"/Users/" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
testuid) ByteString
"" HasCallStack =>
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
WaiSession SResponse -> ResponseMatcher -> WaiSession ()
`shouldEventuallyRespondWith` ResponseMatcher
404
String
-> ((Application, AcceptanceQueryConfig tag) -> Expectation)
-> SpecWith
(Arg ((Application, AcceptanceQueryConfig tag) -> Expectation))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Group operations" (((Application, AcceptanceQueryConfig tag) -> Expectation)
-> SpecWith
(Arg ((Application, AcceptanceQueryConfig tag) -> Expectation)))
-> ((Application, AcceptanceQueryConfig tag) -> Expectation)
-> SpecWith
(Arg ((Application, AcceptanceQueryConfig tag) -> Expectation))
forall a b. (a -> b) -> a -> b
$ \(Application, AcceptanceQueryConfig tag)
_ -> Expectation
HasCallStack => Expectation
pending
sampleUser1 :: Text -> L.ByteString
sampleUser1 :: Text -> ByteString
sampleUser1 Text
userName1 =
[scim|
{
"schemas": [
"urn:ietf:params:scim:schemas:core:2.0:User",
"urn:ietf:params:scim:schemas:extension:enterprise:2.0:User"],
"externalId": "0a21f0f2-8d2a-4f8e-bf98-7363c4aed4ef",
"userName": #{userName1},
"active": true,
"emails": [{
"primary": true,
"type": "work",
"value": #{userName1 <> "@testuser.com"}
}],
"meta": {
"resourceType": "User"
},
"name": {
"formatted": "givenName familyName",
"familyName": "familyName",
"givenName": "givenName"
},
"roles": []
}
|]