{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.WorkSpacesWeb.UpdateUserSettings
(
UpdateUserSettings (..),
newUpdateUserSettings,
updateUserSettings_clientToken,
updateUserSettings_copyAllowed,
updateUserSettings_disconnectTimeoutInMinutes,
updateUserSettings_downloadAllowed,
updateUserSettings_idleDisconnectTimeoutInMinutes,
updateUserSettings_pasteAllowed,
updateUserSettings_printAllowed,
updateUserSettings_uploadAllowed,
updateUserSettings_userSettingsArn,
UpdateUserSettingsResponse (..),
newUpdateUserSettingsResponse,
updateUserSettingsResponse_httpStatus,
updateUserSettingsResponse_userSettings,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.WorkSpacesWeb.Types
data UpdateUserSettings = UpdateUserSettings'
{
UpdateUserSettings -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
UpdateUserSettings -> Maybe EnabledType
copyAllowed :: Prelude.Maybe EnabledType,
UpdateUserSettings -> Maybe Natural
disconnectTimeoutInMinutes :: Prelude.Maybe Prelude.Natural,
UpdateUserSettings -> Maybe EnabledType
downloadAllowed :: Prelude.Maybe EnabledType,
UpdateUserSettings -> Maybe Natural
idleDisconnectTimeoutInMinutes :: Prelude.Maybe Prelude.Natural,
UpdateUserSettings -> Maybe EnabledType
pasteAllowed :: Prelude.Maybe EnabledType,
UpdateUserSettings -> Maybe EnabledType
printAllowed :: Prelude.Maybe EnabledType,
UpdateUserSettings -> Maybe EnabledType
uploadAllowed :: Prelude.Maybe EnabledType,
UpdateUserSettings -> Text
userSettingsArn :: Prelude.Text
}
deriving (UpdateUserSettings -> UpdateUserSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserSettings -> UpdateUserSettings -> Bool
$c/= :: UpdateUserSettings -> UpdateUserSettings -> Bool
== :: UpdateUserSettings -> UpdateUserSettings -> Bool
$c== :: UpdateUserSettings -> UpdateUserSettings -> Bool
Prelude.Eq, ReadPrec [UpdateUserSettings]
ReadPrec UpdateUserSettings
Int -> ReadS UpdateUserSettings
ReadS [UpdateUserSettings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUserSettings]
$creadListPrec :: ReadPrec [UpdateUserSettings]
readPrec :: ReadPrec UpdateUserSettings
$creadPrec :: ReadPrec UpdateUserSettings
readList :: ReadS [UpdateUserSettings]
$creadList :: ReadS [UpdateUserSettings]
readsPrec :: Int -> ReadS UpdateUserSettings
$creadsPrec :: Int -> ReadS UpdateUserSettings
Prelude.Read, Int -> UpdateUserSettings -> ShowS
[UpdateUserSettings] -> ShowS
UpdateUserSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserSettings] -> ShowS
$cshowList :: [UpdateUserSettings] -> ShowS
show :: UpdateUserSettings -> String
$cshow :: UpdateUserSettings -> String
showsPrec :: Int -> UpdateUserSettings -> ShowS
$cshowsPrec :: Int -> UpdateUserSettings -> ShowS
Prelude.Show, forall x. Rep UpdateUserSettings x -> UpdateUserSettings
forall x. UpdateUserSettings -> Rep UpdateUserSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateUserSettings x -> UpdateUserSettings
$cfrom :: forall x. UpdateUserSettings -> Rep UpdateUserSettings x
Prelude.Generic)
newUpdateUserSettings ::
Prelude.Text ->
UpdateUserSettings
newUpdateUserSettings :: Text -> UpdateUserSettings
newUpdateUserSettings Text
pUserSettingsArn_ =
UpdateUserSettings'
{ $sel:clientToken:UpdateUserSettings' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
$sel:copyAllowed:UpdateUserSettings' :: Maybe EnabledType
copyAllowed = forall a. Maybe a
Prelude.Nothing,
$sel:disconnectTimeoutInMinutes:UpdateUserSettings' :: Maybe Natural
disconnectTimeoutInMinutes = forall a. Maybe a
Prelude.Nothing,
$sel:downloadAllowed:UpdateUserSettings' :: Maybe EnabledType
downloadAllowed = forall a. Maybe a
Prelude.Nothing,
$sel:idleDisconnectTimeoutInMinutes:UpdateUserSettings' :: Maybe Natural
idleDisconnectTimeoutInMinutes = forall a. Maybe a
Prelude.Nothing,
$sel:pasteAllowed:UpdateUserSettings' :: Maybe EnabledType
pasteAllowed = forall a. Maybe a
Prelude.Nothing,
$sel:printAllowed:UpdateUserSettings' :: Maybe EnabledType
printAllowed = forall a. Maybe a
Prelude.Nothing,
$sel:uploadAllowed:UpdateUserSettings' :: Maybe EnabledType
uploadAllowed = forall a. Maybe a
Prelude.Nothing,
$sel:userSettingsArn:UpdateUserSettings' :: Text
userSettingsArn = Text
pUserSettingsArn_
}
updateUserSettings_clientToken :: Lens.Lens' UpdateUserSettings (Prelude.Maybe Prelude.Text)
updateUserSettings_clientToken :: Lens' UpdateUserSettings (Maybe Text)
updateUserSettings_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:UpdateUserSettings' :: UpdateUserSettings -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Maybe Text
a -> UpdateUserSettings
s {$sel:clientToken:UpdateUserSettings' :: Maybe Text
clientToken = Maybe Text
a} :: UpdateUserSettings)
updateUserSettings_copyAllowed :: Lens.Lens' UpdateUserSettings (Prelude.Maybe EnabledType)
updateUserSettings_copyAllowed :: Lens' UpdateUserSettings (Maybe EnabledType)
updateUserSettings_copyAllowed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Maybe EnabledType
copyAllowed :: Maybe EnabledType
$sel:copyAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
copyAllowed} -> Maybe EnabledType
copyAllowed) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Maybe EnabledType
a -> UpdateUserSettings
s {$sel:copyAllowed:UpdateUserSettings' :: Maybe EnabledType
copyAllowed = Maybe EnabledType
a} :: UpdateUserSettings)
updateUserSettings_disconnectTimeoutInMinutes :: Lens.Lens' UpdateUserSettings (Prelude.Maybe Prelude.Natural)
updateUserSettings_disconnectTimeoutInMinutes :: Lens' UpdateUserSettings (Maybe Natural)
updateUserSettings_disconnectTimeoutInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Maybe Natural
disconnectTimeoutInMinutes :: Maybe Natural
$sel:disconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
disconnectTimeoutInMinutes} -> Maybe Natural
disconnectTimeoutInMinutes) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Maybe Natural
a -> UpdateUserSettings
s {$sel:disconnectTimeoutInMinutes:UpdateUserSettings' :: Maybe Natural
disconnectTimeoutInMinutes = Maybe Natural
a} :: UpdateUserSettings)
updateUserSettings_downloadAllowed :: Lens.Lens' UpdateUserSettings (Prelude.Maybe EnabledType)
updateUserSettings_downloadAllowed :: Lens' UpdateUserSettings (Maybe EnabledType)
updateUserSettings_downloadAllowed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Maybe EnabledType
downloadAllowed :: Maybe EnabledType
$sel:downloadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
downloadAllowed} -> Maybe EnabledType
downloadAllowed) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Maybe EnabledType
a -> UpdateUserSettings
s {$sel:downloadAllowed:UpdateUserSettings' :: Maybe EnabledType
downloadAllowed = Maybe EnabledType
a} :: UpdateUserSettings)
updateUserSettings_idleDisconnectTimeoutInMinutes :: Lens.Lens' UpdateUserSettings (Prelude.Maybe Prelude.Natural)
updateUserSettings_idleDisconnectTimeoutInMinutes :: Lens' UpdateUserSettings (Maybe Natural)
updateUserSettings_idleDisconnectTimeoutInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Maybe Natural
idleDisconnectTimeoutInMinutes :: Maybe Natural
$sel:idleDisconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
idleDisconnectTimeoutInMinutes} -> Maybe Natural
idleDisconnectTimeoutInMinutes) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Maybe Natural
a -> UpdateUserSettings
s {$sel:idleDisconnectTimeoutInMinutes:UpdateUserSettings' :: Maybe Natural
idleDisconnectTimeoutInMinutes = Maybe Natural
a} :: UpdateUserSettings)
updateUserSettings_pasteAllowed :: Lens.Lens' UpdateUserSettings (Prelude.Maybe EnabledType)
updateUserSettings_pasteAllowed :: Lens' UpdateUserSettings (Maybe EnabledType)
updateUserSettings_pasteAllowed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Maybe EnabledType
pasteAllowed :: Maybe EnabledType
$sel:pasteAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
pasteAllowed} -> Maybe EnabledType
pasteAllowed) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Maybe EnabledType
a -> UpdateUserSettings
s {$sel:pasteAllowed:UpdateUserSettings' :: Maybe EnabledType
pasteAllowed = Maybe EnabledType
a} :: UpdateUserSettings)
updateUserSettings_printAllowed :: Lens.Lens' UpdateUserSettings (Prelude.Maybe EnabledType)
updateUserSettings_printAllowed :: Lens' UpdateUserSettings (Maybe EnabledType)
updateUserSettings_printAllowed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Maybe EnabledType
printAllowed :: Maybe EnabledType
$sel:printAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
printAllowed} -> Maybe EnabledType
printAllowed) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Maybe EnabledType
a -> UpdateUserSettings
s {$sel:printAllowed:UpdateUserSettings' :: Maybe EnabledType
printAllowed = Maybe EnabledType
a} :: UpdateUserSettings)
updateUserSettings_uploadAllowed :: Lens.Lens' UpdateUserSettings (Prelude.Maybe EnabledType)
updateUserSettings_uploadAllowed :: Lens' UpdateUserSettings (Maybe EnabledType)
updateUserSettings_uploadAllowed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Maybe EnabledType
uploadAllowed :: Maybe EnabledType
$sel:uploadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
uploadAllowed} -> Maybe EnabledType
uploadAllowed) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Maybe EnabledType
a -> UpdateUserSettings
s {$sel:uploadAllowed:UpdateUserSettings' :: Maybe EnabledType
uploadAllowed = Maybe EnabledType
a} :: UpdateUserSettings)
updateUserSettings_userSettingsArn :: Lens.Lens' UpdateUserSettings Prelude.Text
updateUserSettings_userSettingsArn :: Lens' UpdateUserSettings Text
updateUserSettings_userSettingsArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettings' {Text
userSettingsArn :: Text
$sel:userSettingsArn:UpdateUserSettings' :: UpdateUserSettings -> Text
userSettingsArn} -> Text
userSettingsArn) (\s :: UpdateUserSettings
s@UpdateUserSettings' {} Text
a -> UpdateUserSettings
s {$sel:userSettingsArn:UpdateUserSettings' :: Text
userSettingsArn = Text
a} :: UpdateUserSettings)
instance Core.AWSRequest UpdateUserSettings where
type
AWSResponse UpdateUserSettings =
UpdateUserSettingsResponse
request :: (Service -> Service)
-> UpdateUserSettings -> Request UpdateUserSettings
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateUserSettings
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse UpdateUserSettings)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Int -> UserSettings -> UpdateUserSettingsResponse
UpdateUserSettingsResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"userSettings")
)
instance Prelude.Hashable UpdateUserSettings where
hashWithSalt :: Int -> UpdateUserSettings -> Int
hashWithSalt Int
_salt UpdateUserSettings' {Maybe Natural
Maybe Text
Maybe EnabledType
Text
userSettingsArn :: Text
uploadAllowed :: Maybe EnabledType
printAllowed :: Maybe EnabledType
pasteAllowed :: Maybe EnabledType
idleDisconnectTimeoutInMinutes :: Maybe Natural
downloadAllowed :: Maybe EnabledType
disconnectTimeoutInMinutes :: Maybe Natural
copyAllowed :: Maybe EnabledType
clientToken :: Maybe Text
$sel:userSettingsArn:UpdateUserSettings' :: UpdateUserSettings -> Text
$sel:uploadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:printAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:pasteAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:idleDisconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
$sel:downloadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:disconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
$sel:copyAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:clientToken:UpdateUserSettings' :: UpdateUserSettings -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnabledType
copyAllowed
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
disconnectTimeoutInMinutes
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnabledType
downloadAllowed
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
idleDisconnectTimeoutInMinutes
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnabledType
pasteAllowed
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnabledType
printAllowed
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnabledType
uploadAllowed
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userSettingsArn
instance Prelude.NFData UpdateUserSettings where
rnf :: UpdateUserSettings -> ()
rnf UpdateUserSettings' {Maybe Natural
Maybe Text
Maybe EnabledType
Text
userSettingsArn :: Text
uploadAllowed :: Maybe EnabledType
printAllowed :: Maybe EnabledType
pasteAllowed :: Maybe EnabledType
idleDisconnectTimeoutInMinutes :: Maybe Natural
downloadAllowed :: Maybe EnabledType
disconnectTimeoutInMinutes :: Maybe Natural
copyAllowed :: Maybe EnabledType
clientToken :: Maybe Text
$sel:userSettingsArn:UpdateUserSettings' :: UpdateUserSettings -> Text
$sel:uploadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:printAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:pasteAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:idleDisconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
$sel:downloadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:disconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
$sel:copyAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:clientToken:UpdateUserSettings' :: UpdateUserSettings -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnabledType
copyAllowed
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
disconnectTimeoutInMinutes
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnabledType
downloadAllowed
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
idleDisconnectTimeoutInMinutes
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnabledType
pasteAllowed
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnabledType
printAllowed
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnabledType
uploadAllowed
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userSettingsArn
instance Data.ToHeaders UpdateUserSettings where
toHeaders :: UpdateUserSettings -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON UpdateUserSettings where
toJSON :: UpdateUserSettings -> Value
toJSON UpdateUserSettings' {Maybe Natural
Maybe Text
Maybe EnabledType
Text
userSettingsArn :: Text
uploadAllowed :: Maybe EnabledType
printAllowed :: Maybe EnabledType
pasteAllowed :: Maybe EnabledType
idleDisconnectTimeoutInMinutes :: Maybe Natural
downloadAllowed :: Maybe EnabledType
disconnectTimeoutInMinutes :: Maybe Natural
copyAllowed :: Maybe EnabledType
clientToken :: Maybe Text
$sel:userSettingsArn:UpdateUserSettings' :: UpdateUserSettings -> Text
$sel:uploadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:printAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:pasteAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:idleDisconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
$sel:downloadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:disconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
$sel:copyAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:clientToken:UpdateUserSettings' :: UpdateUserSettings -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"clientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
clientToken,
(Key
"copyAllowed" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnabledType
copyAllowed,
(Key
"disconnectTimeoutInMinutes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
disconnectTimeoutInMinutes,
(Key
"downloadAllowed" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnabledType
downloadAllowed,
(Key
"idleDisconnectTimeoutInMinutes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
idleDisconnectTimeoutInMinutes,
(Key
"pasteAllowed" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnabledType
pasteAllowed,
(Key
"printAllowed" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnabledType
printAllowed,
(Key
"uploadAllowed" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnabledType
uploadAllowed
]
)
instance Data.ToPath UpdateUserSettings where
toPath :: UpdateUserSettings -> ByteString
toPath UpdateUserSettings' {Maybe Natural
Maybe Text
Maybe EnabledType
Text
userSettingsArn :: Text
uploadAllowed :: Maybe EnabledType
printAllowed :: Maybe EnabledType
pasteAllowed :: Maybe EnabledType
idleDisconnectTimeoutInMinutes :: Maybe Natural
downloadAllowed :: Maybe EnabledType
disconnectTimeoutInMinutes :: Maybe Natural
copyAllowed :: Maybe EnabledType
clientToken :: Maybe Text
$sel:userSettingsArn:UpdateUserSettings' :: UpdateUserSettings -> Text
$sel:uploadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:printAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:pasteAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:idleDisconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
$sel:downloadAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:disconnectTimeoutInMinutes:UpdateUserSettings' :: UpdateUserSettings -> Maybe Natural
$sel:copyAllowed:UpdateUserSettings' :: UpdateUserSettings -> Maybe EnabledType
$sel:clientToken:UpdateUserSettings' :: UpdateUserSettings -> Maybe Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/userSettings/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
userSettingsArn]
instance Data.ToQuery UpdateUserSettings where
toQuery :: UpdateUserSettings -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateUserSettingsResponse = UpdateUserSettingsResponse'
{
UpdateUserSettingsResponse -> Int
httpStatus :: Prelude.Int,
UpdateUserSettingsResponse -> UserSettings
userSettings :: UserSettings
}
deriving (UpdateUserSettingsResponse -> UpdateUserSettingsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserSettingsResponse -> UpdateUserSettingsResponse -> Bool
$c/= :: UpdateUserSettingsResponse -> UpdateUserSettingsResponse -> Bool
== :: UpdateUserSettingsResponse -> UpdateUserSettingsResponse -> Bool
$c== :: UpdateUserSettingsResponse -> UpdateUserSettingsResponse -> Bool
Prelude.Eq, ReadPrec [UpdateUserSettingsResponse]
ReadPrec UpdateUserSettingsResponse
Int -> ReadS UpdateUserSettingsResponse
ReadS [UpdateUserSettingsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUserSettingsResponse]
$creadListPrec :: ReadPrec [UpdateUserSettingsResponse]
readPrec :: ReadPrec UpdateUserSettingsResponse
$creadPrec :: ReadPrec UpdateUserSettingsResponse
readList :: ReadS [UpdateUserSettingsResponse]
$creadList :: ReadS [UpdateUserSettingsResponse]
readsPrec :: Int -> ReadS UpdateUserSettingsResponse
$creadsPrec :: Int -> ReadS UpdateUserSettingsResponse
Prelude.Read, Int -> UpdateUserSettingsResponse -> ShowS
[UpdateUserSettingsResponse] -> ShowS
UpdateUserSettingsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserSettingsResponse] -> ShowS
$cshowList :: [UpdateUserSettingsResponse] -> ShowS
show :: UpdateUserSettingsResponse -> String
$cshow :: UpdateUserSettingsResponse -> String
showsPrec :: Int -> UpdateUserSettingsResponse -> ShowS
$cshowsPrec :: Int -> UpdateUserSettingsResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateUserSettingsResponse x -> UpdateUserSettingsResponse
forall x.
UpdateUserSettingsResponse -> Rep UpdateUserSettingsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateUserSettingsResponse x -> UpdateUserSettingsResponse
$cfrom :: forall x.
UpdateUserSettingsResponse -> Rep UpdateUserSettingsResponse x
Prelude.Generic)
newUpdateUserSettingsResponse ::
Prelude.Int ->
UserSettings ->
UpdateUserSettingsResponse
newUpdateUserSettingsResponse :: Int -> UserSettings -> UpdateUserSettingsResponse
newUpdateUserSettingsResponse
Int
pHttpStatus_
UserSettings
pUserSettings_ =
UpdateUserSettingsResponse'
{ $sel:httpStatus:UpdateUserSettingsResponse' :: Int
httpStatus =
Int
pHttpStatus_,
$sel:userSettings:UpdateUserSettingsResponse' :: UserSettings
userSettings = UserSettings
pUserSettings_
}
updateUserSettingsResponse_httpStatus :: Lens.Lens' UpdateUserSettingsResponse Prelude.Int
updateUserSettingsResponse_httpStatus :: Lens' UpdateUserSettingsResponse Int
updateUserSettingsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettingsResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateUserSettingsResponse' :: UpdateUserSettingsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateUserSettingsResponse
s@UpdateUserSettingsResponse' {} Int
a -> UpdateUserSettingsResponse
s {$sel:httpStatus:UpdateUserSettingsResponse' :: Int
httpStatus = Int
a} :: UpdateUserSettingsResponse)
updateUserSettingsResponse_userSettings :: Lens.Lens' UpdateUserSettingsResponse UserSettings
updateUserSettingsResponse_userSettings :: Lens' UpdateUserSettingsResponse UserSettings
updateUserSettingsResponse_userSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserSettingsResponse' {UserSettings
userSettings :: UserSettings
$sel:userSettings:UpdateUserSettingsResponse' :: UpdateUserSettingsResponse -> UserSettings
userSettings} -> UserSettings
userSettings) (\s :: UpdateUserSettingsResponse
s@UpdateUserSettingsResponse' {} UserSettings
a -> UpdateUserSettingsResponse
s {$sel:userSettings:UpdateUserSettingsResponse' :: UserSettings
userSettings = UserSettings
a} :: UpdateUserSettingsResponse)
instance Prelude.NFData UpdateUserSettingsResponse where
rnf :: UpdateUserSettingsResponse -> ()
rnf UpdateUserSettingsResponse' {Int
UserSettings
userSettings :: UserSettings
httpStatus :: Int
$sel:userSettings:UpdateUserSettingsResponse' :: UpdateUserSettingsResponse -> UserSettings
$sel:httpStatus:UpdateUserSettingsResponse' :: UpdateUserSettingsResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf UserSettings
userSettings