{-# 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.CodeBuild.ListSharedProjects
(
ListSharedProjects (..),
newListSharedProjects,
listSharedProjects_maxResults,
listSharedProjects_nextToken,
listSharedProjects_sortBy,
listSharedProjects_sortOrder,
ListSharedProjectsResponse (..),
newListSharedProjectsResponse,
listSharedProjectsResponse_nextToken,
listSharedProjectsResponse_projects,
listSharedProjectsResponse_httpStatus,
)
where
import Amazonka.CodeBuild.Types
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
data ListSharedProjects = ListSharedProjects'
{
ListSharedProjects -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
ListSharedProjects -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListSharedProjects -> Maybe SharedResourceSortByType
sortBy :: Prelude.Maybe SharedResourceSortByType,
ListSharedProjects -> Maybe SortOrderType
sortOrder :: Prelude.Maybe SortOrderType
}
deriving (ListSharedProjects -> ListSharedProjects -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSharedProjects -> ListSharedProjects -> Bool
$c/= :: ListSharedProjects -> ListSharedProjects -> Bool
== :: ListSharedProjects -> ListSharedProjects -> Bool
$c== :: ListSharedProjects -> ListSharedProjects -> Bool
Prelude.Eq, ReadPrec [ListSharedProjects]
ReadPrec ListSharedProjects
Int -> ReadS ListSharedProjects
ReadS [ListSharedProjects]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSharedProjects]
$creadListPrec :: ReadPrec [ListSharedProjects]
readPrec :: ReadPrec ListSharedProjects
$creadPrec :: ReadPrec ListSharedProjects
readList :: ReadS [ListSharedProjects]
$creadList :: ReadS [ListSharedProjects]
readsPrec :: Int -> ReadS ListSharedProjects
$creadsPrec :: Int -> ReadS ListSharedProjects
Prelude.Read, Int -> ListSharedProjects -> ShowS
[ListSharedProjects] -> ShowS
ListSharedProjects -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSharedProjects] -> ShowS
$cshowList :: [ListSharedProjects] -> ShowS
show :: ListSharedProjects -> String
$cshow :: ListSharedProjects -> String
showsPrec :: Int -> ListSharedProjects -> ShowS
$cshowsPrec :: Int -> ListSharedProjects -> ShowS
Prelude.Show, forall x. Rep ListSharedProjects x -> ListSharedProjects
forall x. ListSharedProjects -> Rep ListSharedProjects x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListSharedProjects x -> ListSharedProjects
$cfrom :: forall x. ListSharedProjects -> Rep ListSharedProjects x
Prelude.Generic)
newListSharedProjects ::
ListSharedProjects
newListSharedProjects :: ListSharedProjects
newListSharedProjects =
ListSharedProjects'
{ $sel:maxResults:ListSharedProjects' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListSharedProjects' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:sortBy:ListSharedProjects' :: Maybe SharedResourceSortByType
sortBy = forall a. Maybe a
Prelude.Nothing,
$sel:sortOrder:ListSharedProjects' :: Maybe SortOrderType
sortOrder = forall a. Maybe a
Prelude.Nothing
}
listSharedProjects_maxResults :: Lens.Lens' ListSharedProjects (Prelude.Maybe Prelude.Natural)
listSharedProjects_maxResults :: Lens' ListSharedProjects (Maybe Natural)
listSharedProjects_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSharedProjects' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListSharedProjects' :: ListSharedProjects -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListSharedProjects
s@ListSharedProjects' {} Maybe Natural
a -> ListSharedProjects
s {$sel:maxResults:ListSharedProjects' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListSharedProjects)
listSharedProjects_nextToken :: Lens.Lens' ListSharedProjects (Prelude.Maybe Prelude.Text)
listSharedProjects_nextToken :: Lens' ListSharedProjects (Maybe Text)
listSharedProjects_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSharedProjects' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSharedProjects' :: ListSharedProjects -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSharedProjects
s@ListSharedProjects' {} Maybe Text
a -> ListSharedProjects
s {$sel:nextToken:ListSharedProjects' :: Maybe Text
nextToken = Maybe Text
a} :: ListSharedProjects)
listSharedProjects_sortBy :: Lens.Lens' ListSharedProjects (Prelude.Maybe SharedResourceSortByType)
listSharedProjects_sortBy :: Lens' ListSharedProjects (Maybe SharedResourceSortByType)
listSharedProjects_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSharedProjects' {Maybe SharedResourceSortByType
sortBy :: Maybe SharedResourceSortByType
$sel:sortBy:ListSharedProjects' :: ListSharedProjects -> Maybe SharedResourceSortByType
sortBy} -> Maybe SharedResourceSortByType
sortBy) (\s :: ListSharedProjects
s@ListSharedProjects' {} Maybe SharedResourceSortByType
a -> ListSharedProjects
s {$sel:sortBy:ListSharedProjects' :: Maybe SharedResourceSortByType
sortBy = Maybe SharedResourceSortByType
a} :: ListSharedProjects)
listSharedProjects_sortOrder :: Lens.Lens' ListSharedProjects (Prelude.Maybe SortOrderType)
listSharedProjects_sortOrder :: Lens' ListSharedProjects (Maybe SortOrderType)
listSharedProjects_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSharedProjects' {Maybe SortOrderType
sortOrder :: Maybe SortOrderType
$sel:sortOrder:ListSharedProjects' :: ListSharedProjects -> Maybe SortOrderType
sortOrder} -> Maybe SortOrderType
sortOrder) (\s :: ListSharedProjects
s@ListSharedProjects' {} Maybe SortOrderType
a -> ListSharedProjects
s {$sel:sortOrder:ListSharedProjects' :: Maybe SortOrderType
sortOrder = Maybe SortOrderType
a} :: ListSharedProjects)
instance Core.AWSPager ListSharedProjects where
page :: ListSharedProjects
-> AWSResponse ListSharedProjects -> Maybe ListSharedProjects
page ListSharedProjects
rq AWSResponse ListSharedProjects
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListSharedProjects
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSharedProjectsResponse (Maybe Text)
listSharedProjectsResponse_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 ListSharedProjects
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSharedProjectsResponse (Maybe (NonEmpty Text))
listSharedProjectsResponse_projects
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall l. IsList l => l -> [Item l]
Prelude.toList
) =
forall a. Maybe a
Prelude.Nothing
| Bool
Prelude.otherwise =
forall a. a -> Maybe a
Prelude.Just
forall a b. (a -> b) -> a -> b
Prelude.$ ListSharedProjects
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListSharedProjects (Maybe Text)
listSharedProjects_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListSharedProjects
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSharedProjectsResponse (Maybe Text)
listSharedProjectsResponse_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 ListSharedProjects where
type
AWSResponse ListSharedProjects =
ListSharedProjectsResponse
request :: (Service -> Service)
-> ListSharedProjects -> Request ListSharedProjects
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListSharedProjects
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse ListSharedProjects)))
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
-> Maybe (NonEmpty Text) -> Int -> ListSharedProjectsResponse
ListSharedProjectsResponse'
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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"projects")
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))
)
instance Prelude.Hashable ListSharedProjects where
hashWithSalt :: Int -> ListSharedProjects -> Int
hashWithSalt Int
_salt ListSharedProjects' {Maybe Natural
Maybe Text
Maybe SharedResourceSortByType
Maybe SortOrderType
sortOrder :: Maybe SortOrderType
sortBy :: Maybe SharedResourceSortByType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:sortOrder:ListSharedProjects' :: ListSharedProjects -> Maybe SortOrderType
$sel:sortBy:ListSharedProjects' :: ListSharedProjects -> Maybe SharedResourceSortByType
$sel:nextToken:ListSharedProjects' :: ListSharedProjects -> Maybe Text
$sel:maxResults:ListSharedProjects' :: ListSharedProjects -> Maybe Natural
..} =
Int
_salt
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 SharedResourceSortByType
sortBy
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrderType
sortOrder
instance Prelude.NFData ListSharedProjects where
rnf :: ListSharedProjects -> ()
rnf ListSharedProjects' {Maybe Natural
Maybe Text
Maybe SharedResourceSortByType
Maybe SortOrderType
sortOrder :: Maybe SortOrderType
sortBy :: Maybe SharedResourceSortByType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:sortOrder:ListSharedProjects' :: ListSharedProjects -> Maybe SortOrderType
$sel:sortBy:ListSharedProjects' :: ListSharedProjects -> Maybe SharedResourceSortByType
$sel:nextToken:ListSharedProjects' :: ListSharedProjects -> Maybe Text
$sel:maxResults:ListSharedProjects' :: ListSharedProjects -> Maybe Natural
..} =
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 SharedResourceSortByType
sortBy
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SortOrderType
sortOrder
instance Data.ToHeaders ListSharedProjects where
toHeaders :: ListSharedProjects -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"CodeBuild_20161006.ListSharedProjects" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON ListSharedProjects where
toJSON :: ListSharedProjects -> Value
toJSON ListSharedProjects' {Maybe Natural
Maybe Text
Maybe SharedResourceSortByType
Maybe SortOrderType
sortOrder :: Maybe SortOrderType
sortBy :: Maybe SharedResourceSortByType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:sortOrder:ListSharedProjects' :: ListSharedProjects -> Maybe SortOrderType
$sel:sortBy:ListSharedProjects' :: ListSharedProjects -> Maybe SharedResourceSortByType
$sel:nextToken:ListSharedProjects' :: ListSharedProjects -> Maybe Text
$sel:maxResults:ListSharedProjects' :: ListSharedProjects -> Maybe Natural
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"maxResults" 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
maxResults,
(Key
"nextToken" 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
nextToken,
(Key
"sortBy" 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 SharedResourceSortByType
sortBy,
(Key
"sortOrder" 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 SortOrderType
sortOrder
]
)
instance Data.ToPath ListSharedProjects where
toPath :: ListSharedProjects -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListSharedProjects where
toQuery :: ListSharedProjects -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListSharedProjectsResponse = ListSharedProjectsResponse'
{
ListSharedProjectsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListSharedProjectsResponse -> Maybe (NonEmpty Text)
projects :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
ListSharedProjectsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListSharedProjectsResponse -> ListSharedProjectsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSharedProjectsResponse -> ListSharedProjectsResponse -> Bool
$c/= :: ListSharedProjectsResponse -> ListSharedProjectsResponse -> Bool
== :: ListSharedProjectsResponse -> ListSharedProjectsResponse -> Bool
$c== :: ListSharedProjectsResponse -> ListSharedProjectsResponse -> Bool
Prelude.Eq, ReadPrec [ListSharedProjectsResponse]
ReadPrec ListSharedProjectsResponse
Int -> ReadS ListSharedProjectsResponse
ReadS [ListSharedProjectsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSharedProjectsResponse]
$creadListPrec :: ReadPrec [ListSharedProjectsResponse]
readPrec :: ReadPrec ListSharedProjectsResponse
$creadPrec :: ReadPrec ListSharedProjectsResponse
readList :: ReadS [ListSharedProjectsResponse]
$creadList :: ReadS [ListSharedProjectsResponse]
readsPrec :: Int -> ReadS ListSharedProjectsResponse
$creadsPrec :: Int -> ReadS ListSharedProjectsResponse
Prelude.Read, Int -> ListSharedProjectsResponse -> ShowS
[ListSharedProjectsResponse] -> ShowS
ListSharedProjectsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSharedProjectsResponse] -> ShowS
$cshowList :: [ListSharedProjectsResponse] -> ShowS
show :: ListSharedProjectsResponse -> String
$cshow :: ListSharedProjectsResponse -> String
showsPrec :: Int -> ListSharedProjectsResponse -> ShowS
$cshowsPrec :: Int -> ListSharedProjectsResponse -> ShowS
Prelude.Show, forall x.
Rep ListSharedProjectsResponse x -> ListSharedProjectsResponse
forall x.
ListSharedProjectsResponse -> Rep ListSharedProjectsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListSharedProjectsResponse x -> ListSharedProjectsResponse
$cfrom :: forall x.
ListSharedProjectsResponse -> Rep ListSharedProjectsResponse x
Prelude.Generic)
newListSharedProjectsResponse ::
Prelude.Int ->
ListSharedProjectsResponse
newListSharedProjectsResponse :: Int -> ListSharedProjectsResponse
newListSharedProjectsResponse Int
pHttpStatus_ =
ListSharedProjectsResponse'
{ $sel:nextToken:ListSharedProjectsResponse' :: Maybe Text
nextToken =
forall a. Maybe a
Prelude.Nothing,
$sel:projects:ListSharedProjectsResponse' :: Maybe (NonEmpty Text)
projects = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListSharedProjectsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listSharedProjectsResponse_nextToken :: Lens.Lens' ListSharedProjectsResponse (Prelude.Maybe Prelude.Text)
listSharedProjectsResponse_nextToken :: Lens' ListSharedProjectsResponse (Maybe Text)
listSharedProjectsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSharedProjectsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSharedProjectsResponse' :: ListSharedProjectsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSharedProjectsResponse
s@ListSharedProjectsResponse' {} Maybe Text
a -> ListSharedProjectsResponse
s {$sel:nextToken:ListSharedProjectsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListSharedProjectsResponse)
listSharedProjectsResponse_projects :: Lens.Lens' ListSharedProjectsResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
listSharedProjectsResponse_projects :: Lens' ListSharedProjectsResponse (Maybe (NonEmpty Text))
listSharedProjectsResponse_projects = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSharedProjectsResponse' {Maybe (NonEmpty Text)
projects :: Maybe (NonEmpty Text)
$sel:projects:ListSharedProjectsResponse' :: ListSharedProjectsResponse -> Maybe (NonEmpty Text)
projects} -> Maybe (NonEmpty Text)
projects) (\s :: ListSharedProjectsResponse
s@ListSharedProjectsResponse' {} Maybe (NonEmpty Text)
a -> ListSharedProjectsResponse
s {$sel:projects:ListSharedProjectsResponse' :: Maybe (NonEmpty Text)
projects = Maybe (NonEmpty Text)
a} :: ListSharedProjectsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
listSharedProjectsResponse_httpStatus :: Lens.Lens' ListSharedProjectsResponse Prelude.Int
listSharedProjectsResponse_httpStatus :: Lens' ListSharedProjectsResponse Int
listSharedProjectsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSharedProjectsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListSharedProjectsResponse' :: ListSharedProjectsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListSharedProjectsResponse
s@ListSharedProjectsResponse' {} Int
a -> ListSharedProjectsResponse
s {$sel:httpStatus:ListSharedProjectsResponse' :: Int
httpStatus = Int
a} :: ListSharedProjectsResponse)
instance Prelude.NFData ListSharedProjectsResponse where
rnf :: ListSharedProjectsResponse -> ()
rnf ListSharedProjectsResponse' {Int
Maybe (NonEmpty Text)
Maybe Text
httpStatus :: Int
projects :: Maybe (NonEmpty Text)
nextToken :: Maybe Text
$sel:httpStatus:ListSharedProjectsResponse' :: ListSharedProjectsResponse -> Int
$sel:projects:ListSharedProjectsResponse' :: ListSharedProjectsResponse -> Maybe (NonEmpty Text)
$sel:nextToken:ListSharedProjectsResponse' :: ListSharedProjectsResponse -> 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 Maybe (NonEmpty Text)
projects
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus