{-# 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.Grafana.ListPermissions
(
ListPermissions (..),
newListPermissions,
listPermissions_groupId,
listPermissions_maxResults,
listPermissions_nextToken,
listPermissions_userId,
listPermissions_userType,
listPermissions_workspaceId,
ListPermissionsResponse (..),
newListPermissionsResponse,
listPermissionsResponse_nextToken,
listPermissionsResponse_httpStatus,
listPermissionsResponse_permissions,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Grafana.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data ListPermissions = ListPermissions'
{
ListPermissions -> Maybe Text
groupId :: Prelude.Maybe Prelude.Text,
ListPermissions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
ListPermissions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListPermissions -> Maybe Text
userId :: Prelude.Maybe Prelude.Text,
ListPermissions -> Maybe UserType
userType :: Prelude.Maybe UserType,
ListPermissions -> Text
workspaceId :: Prelude.Text
}
deriving (ListPermissions -> ListPermissions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPermissions -> ListPermissions -> Bool
$c/= :: ListPermissions -> ListPermissions -> Bool
== :: ListPermissions -> ListPermissions -> Bool
$c== :: ListPermissions -> ListPermissions -> Bool
Prelude.Eq, ReadPrec [ListPermissions]
ReadPrec ListPermissions
Int -> ReadS ListPermissions
ReadS [ListPermissions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPermissions]
$creadListPrec :: ReadPrec [ListPermissions]
readPrec :: ReadPrec ListPermissions
$creadPrec :: ReadPrec ListPermissions
readList :: ReadS [ListPermissions]
$creadList :: ReadS [ListPermissions]
readsPrec :: Int -> ReadS ListPermissions
$creadsPrec :: Int -> ReadS ListPermissions
Prelude.Read, Int -> ListPermissions -> ShowS
[ListPermissions] -> ShowS
ListPermissions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPermissions] -> ShowS
$cshowList :: [ListPermissions] -> ShowS
show :: ListPermissions -> String
$cshow :: ListPermissions -> String
showsPrec :: Int -> ListPermissions -> ShowS
$cshowsPrec :: Int -> ListPermissions -> ShowS
Prelude.Show, forall x. Rep ListPermissions x -> ListPermissions
forall x. ListPermissions -> Rep ListPermissions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPermissions x -> ListPermissions
$cfrom :: forall x. ListPermissions -> Rep ListPermissions x
Prelude.Generic)
newListPermissions ::
Prelude.Text ->
ListPermissions
newListPermissions :: Text -> ListPermissions
newListPermissions Text
pWorkspaceId_ =
ListPermissions'
{ $sel:groupId:ListPermissions' :: Maybe Text
groupId = forall a. Maybe a
Prelude.Nothing,
$sel:maxResults:ListPermissions' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListPermissions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:userId:ListPermissions' :: Maybe Text
userId = forall a. Maybe a
Prelude.Nothing,
$sel:userType:ListPermissions' :: Maybe UserType
userType = forall a. Maybe a
Prelude.Nothing,
$sel:workspaceId:ListPermissions' :: Text
workspaceId = Text
pWorkspaceId_
}
listPermissions_groupId :: Lens.Lens' ListPermissions (Prelude.Maybe Prelude.Text)
listPermissions_groupId :: Lens' ListPermissions (Maybe Text)
listPermissions_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissions' {Maybe Text
groupId :: Maybe Text
$sel:groupId:ListPermissions' :: ListPermissions -> Maybe Text
groupId} -> Maybe Text
groupId) (\s :: ListPermissions
s@ListPermissions' {} Maybe Text
a -> ListPermissions
s {$sel:groupId:ListPermissions' :: Maybe Text
groupId = Maybe Text
a} :: ListPermissions)
listPermissions_maxResults :: Lens.Lens' ListPermissions (Prelude.Maybe Prelude.Natural)
listPermissions_maxResults :: Lens' ListPermissions (Maybe Natural)
listPermissions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPermissions' :: ListPermissions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPermissions
s@ListPermissions' {} Maybe Natural
a -> ListPermissions
s {$sel:maxResults:ListPermissions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPermissions)
listPermissions_nextToken :: Lens.Lens' ListPermissions (Prelude.Maybe Prelude.Text)
listPermissions_nextToken :: Lens' ListPermissions (Maybe Text)
listPermissions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPermissions' :: ListPermissions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPermissions
s@ListPermissions' {} Maybe Text
a -> ListPermissions
s {$sel:nextToken:ListPermissions' :: Maybe Text
nextToken = Maybe Text
a} :: ListPermissions)
listPermissions_userId :: Lens.Lens' ListPermissions (Prelude.Maybe Prelude.Text)
listPermissions_userId :: Lens' ListPermissions (Maybe Text)
listPermissions_userId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissions' {Maybe Text
userId :: Maybe Text
$sel:userId:ListPermissions' :: ListPermissions -> Maybe Text
userId} -> Maybe Text
userId) (\s :: ListPermissions
s@ListPermissions' {} Maybe Text
a -> ListPermissions
s {$sel:userId:ListPermissions' :: Maybe Text
userId = Maybe Text
a} :: ListPermissions)
listPermissions_userType :: Lens.Lens' ListPermissions (Prelude.Maybe UserType)
listPermissions_userType :: Lens' ListPermissions (Maybe UserType)
listPermissions_userType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissions' {Maybe UserType
userType :: Maybe UserType
$sel:userType:ListPermissions' :: ListPermissions -> Maybe UserType
userType} -> Maybe UserType
userType) (\s :: ListPermissions
s@ListPermissions' {} Maybe UserType
a -> ListPermissions
s {$sel:userType:ListPermissions' :: Maybe UserType
userType = Maybe UserType
a} :: ListPermissions)
listPermissions_workspaceId :: Lens.Lens' ListPermissions Prelude.Text
listPermissions_workspaceId :: Lens' ListPermissions Text
listPermissions_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissions' {Text
workspaceId :: Text
$sel:workspaceId:ListPermissions' :: ListPermissions -> Text
workspaceId} -> Text
workspaceId) (\s :: ListPermissions
s@ListPermissions' {} Text
a -> ListPermissions
s {$sel:workspaceId:ListPermissions' :: Text
workspaceId = Text
a} :: ListPermissions)
instance Core.AWSPager ListPermissions where
page :: ListPermissions
-> AWSResponse ListPermissions -> Maybe ListPermissions
page ListPermissions
rq AWSResponse ListPermissions
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListPermissions
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPermissionsResponse (Maybe Text)
listPermissionsResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| forall a. AWSTruncated a => a -> Bool
Core.stop
(AWSResponse ListPermissions
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListPermissionsResponse [PermissionEntry]
listPermissionsResponse_permissions) =
forall a. Maybe a
Prelude.Nothing
| Bool
Prelude.otherwise =
forall a. a -> Maybe a
Prelude.Just
forall a b. (a -> b) -> a -> b
Prelude.$ ListPermissions
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListPermissions (Maybe Text)
listPermissions_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListPermissions
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPermissionsResponse (Maybe Text)
listPermissionsResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
instance Core.AWSRequest ListPermissions where
type
AWSResponse ListPermissions =
ListPermissionsResponse
request :: (Service -> Service) -> ListPermissions -> Request ListPermissions
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListPermissions
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListPermissions)))
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 ->
Maybe Text -> Int -> [PermissionEntry] -> ListPermissionsResponse
ListPermissionsResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"nextToken")
forall (f :: * -> *) a b. Applicative f => 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 (Maybe a)
Data..?> Key
"permissions" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
)
instance Prelude.Hashable ListPermissions where
hashWithSalt :: Int -> ListPermissions -> Int
hashWithSalt Int
_salt ListPermissions' {Maybe Natural
Maybe Text
Maybe UserType
Text
workspaceId :: Text
userType :: Maybe UserType
userId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
groupId :: Maybe Text
$sel:workspaceId:ListPermissions' :: ListPermissions -> Text
$sel:userType:ListPermissions' :: ListPermissions -> Maybe UserType
$sel:userId:ListPermissions' :: ListPermissions -> Maybe Text
$sel:nextToken:ListPermissions' :: ListPermissions -> Maybe Text
$sel:maxResults:ListPermissions' :: ListPermissions -> Maybe Natural
$sel:groupId:ListPermissions' :: ListPermissions -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
groupId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
userId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserType
userType
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId
instance Prelude.NFData ListPermissions where
rnf :: ListPermissions -> ()
rnf ListPermissions' {Maybe Natural
Maybe Text
Maybe UserType
Text
workspaceId :: Text
userType :: Maybe UserType
userId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
groupId :: Maybe Text
$sel:workspaceId:ListPermissions' :: ListPermissions -> Text
$sel:userType:ListPermissions' :: ListPermissions -> Maybe UserType
$sel:userId:ListPermissions' :: ListPermissions -> Maybe Text
$sel:nextToken:ListPermissions' :: ListPermissions -> Maybe Text
$sel:maxResults:ListPermissions' :: ListPermissions -> Maybe Natural
$sel:groupId:ListPermissions' :: ListPermissions -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserType
userType
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId
instance Data.ToHeaders ListPermissions where
toHeaders :: ListPermissions -> 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.ToPath ListPermissions where
toPath :: ListPermissions -> ByteString
toPath ListPermissions' {Maybe Natural
Maybe Text
Maybe UserType
Text
workspaceId :: Text
userType :: Maybe UserType
userId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
groupId :: Maybe Text
$sel:workspaceId:ListPermissions' :: ListPermissions -> Text
$sel:userType:ListPermissions' :: ListPermissions -> Maybe UserType
$sel:userId:ListPermissions' :: ListPermissions -> Maybe Text
$sel:nextToken:ListPermissions' :: ListPermissions -> Maybe Text
$sel:maxResults:ListPermissions' :: ListPermissions -> Maybe Natural
$sel:groupId:ListPermissions' :: ListPermissions -> Maybe Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/workspaces/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
workspaceId,
ByteString
"/permissions"
]
instance Data.ToQuery ListPermissions where
toQuery :: ListPermissions -> QueryString
toQuery ListPermissions' {Maybe Natural
Maybe Text
Maybe UserType
Text
workspaceId :: Text
userType :: Maybe UserType
userId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
groupId :: Maybe Text
$sel:workspaceId:ListPermissions' :: ListPermissions -> Text
$sel:userType:ListPermissions' :: ListPermissions -> Maybe UserType
$sel:userId:ListPermissions' :: ListPermissions -> Maybe Text
$sel:nextToken:ListPermissions' :: ListPermissions -> Maybe Text
$sel:maxResults:ListPermissions' :: ListPermissions -> Maybe Natural
$sel:groupId:ListPermissions' :: ListPermissions -> Maybe Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"groupId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
groupId,
ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
ByteString
"userId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
userId,
ByteString
"userType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe UserType
userType
]
data ListPermissionsResponse = ListPermissionsResponse'
{
ListPermissionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListPermissionsResponse -> Int
httpStatus :: Prelude.Int,
ListPermissionsResponse -> [PermissionEntry]
permissions :: [PermissionEntry]
}
deriving (ListPermissionsResponse -> ListPermissionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPermissionsResponse -> ListPermissionsResponse -> Bool
$c/= :: ListPermissionsResponse -> ListPermissionsResponse -> Bool
== :: ListPermissionsResponse -> ListPermissionsResponse -> Bool
$c== :: ListPermissionsResponse -> ListPermissionsResponse -> Bool
Prelude.Eq, ReadPrec [ListPermissionsResponse]
ReadPrec ListPermissionsResponse
Int -> ReadS ListPermissionsResponse
ReadS [ListPermissionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPermissionsResponse]
$creadListPrec :: ReadPrec [ListPermissionsResponse]
readPrec :: ReadPrec ListPermissionsResponse
$creadPrec :: ReadPrec ListPermissionsResponse
readList :: ReadS [ListPermissionsResponse]
$creadList :: ReadS [ListPermissionsResponse]
readsPrec :: Int -> ReadS ListPermissionsResponse
$creadsPrec :: Int -> ReadS ListPermissionsResponse
Prelude.Read, Int -> ListPermissionsResponse -> ShowS
[ListPermissionsResponse] -> ShowS
ListPermissionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPermissionsResponse] -> ShowS
$cshowList :: [ListPermissionsResponse] -> ShowS
show :: ListPermissionsResponse -> String
$cshow :: ListPermissionsResponse -> String
showsPrec :: Int -> ListPermissionsResponse -> ShowS
$cshowsPrec :: Int -> ListPermissionsResponse -> ShowS
Prelude.Show, forall x. Rep ListPermissionsResponse x -> ListPermissionsResponse
forall x. ListPermissionsResponse -> Rep ListPermissionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPermissionsResponse x -> ListPermissionsResponse
$cfrom :: forall x. ListPermissionsResponse -> Rep ListPermissionsResponse x
Prelude.Generic)
newListPermissionsResponse ::
Prelude.Int ->
ListPermissionsResponse
newListPermissionsResponse :: Int -> ListPermissionsResponse
newListPermissionsResponse Int
pHttpStatus_ =
ListPermissionsResponse'
{ $sel:nextToken:ListPermissionsResponse' :: Maybe Text
nextToken =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListPermissionsResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:permissions:ListPermissionsResponse' :: [PermissionEntry]
permissions = forall a. Monoid a => a
Prelude.mempty
}
listPermissionsResponse_nextToken :: Lens.Lens' ListPermissionsResponse (Prelude.Maybe Prelude.Text)
listPermissionsResponse_nextToken :: Lens' ListPermissionsResponse (Maybe Text)
listPermissionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPermissionsResponse' :: ListPermissionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPermissionsResponse
s@ListPermissionsResponse' {} Maybe Text
a -> ListPermissionsResponse
s {$sel:nextToken:ListPermissionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPermissionsResponse)
listPermissionsResponse_httpStatus :: Lens.Lens' ListPermissionsResponse Prelude.Int
listPermissionsResponse_httpStatus :: Lens' ListPermissionsResponse Int
listPermissionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPermissionsResponse' :: ListPermissionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPermissionsResponse
s@ListPermissionsResponse' {} Int
a -> ListPermissionsResponse
s {$sel:httpStatus:ListPermissionsResponse' :: Int
httpStatus = Int
a} :: ListPermissionsResponse)
listPermissionsResponse_permissions :: Lens.Lens' ListPermissionsResponse [PermissionEntry]
listPermissionsResponse_permissions :: Lens' ListPermissionsResponse [PermissionEntry]
listPermissionsResponse_permissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionsResponse' {[PermissionEntry]
permissions :: [PermissionEntry]
$sel:permissions:ListPermissionsResponse' :: ListPermissionsResponse -> [PermissionEntry]
permissions} -> [PermissionEntry]
permissions) (\s :: ListPermissionsResponse
s@ListPermissionsResponse' {} [PermissionEntry]
a -> ListPermissionsResponse
s {$sel:permissions:ListPermissionsResponse' :: [PermissionEntry]
permissions = [PermissionEntry]
a} :: ListPermissionsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
instance Prelude.NFData ListPermissionsResponse where
rnf :: ListPermissionsResponse -> ()
rnf ListPermissionsResponse' {Int
[PermissionEntry]
Maybe Text
permissions :: [PermissionEntry]
httpStatus :: Int
nextToken :: Maybe Text
$sel:permissions:ListPermissionsResponse' :: ListPermissionsResponse -> [PermissionEntry]
$sel:httpStatus:ListPermissionsResponse' :: ListPermissionsResponse -> Int
$sel:nextToken:ListPermissionsResponse' :: ListPermissionsResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` 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 [PermissionEntry]
permissions