{-# 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.CodePipeline.ListPipelines
(
ListPipelines (..),
newListPipelines,
listPipelines_maxResults,
listPipelines_nextToken,
ListPipelinesResponse (..),
newListPipelinesResponse,
listPipelinesResponse_nextToken,
listPipelinesResponse_pipelines,
listPipelinesResponse_httpStatus,
)
where
import Amazonka.CodePipeline.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 ListPipelines = ListPipelines'
{
ListPipelines -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
ListPipelines -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
}
deriving (ListPipelines -> ListPipelines -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPipelines -> ListPipelines -> Bool
$c/= :: ListPipelines -> ListPipelines -> Bool
== :: ListPipelines -> ListPipelines -> Bool
$c== :: ListPipelines -> ListPipelines -> Bool
Prelude.Eq, ReadPrec [ListPipelines]
ReadPrec ListPipelines
Int -> ReadS ListPipelines
ReadS [ListPipelines]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPipelines]
$creadListPrec :: ReadPrec [ListPipelines]
readPrec :: ReadPrec ListPipelines
$creadPrec :: ReadPrec ListPipelines
readList :: ReadS [ListPipelines]
$creadList :: ReadS [ListPipelines]
readsPrec :: Int -> ReadS ListPipelines
$creadsPrec :: Int -> ReadS ListPipelines
Prelude.Read, Int -> ListPipelines -> ShowS
[ListPipelines] -> ShowS
ListPipelines -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPipelines] -> ShowS
$cshowList :: [ListPipelines] -> ShowS
show :: ListPipelines -> String
$cshow :: ListPipelines -> String
showsPrec :: Int -> ListPipelines -> ShowS
$cshowsPrec :: Int -> ListPipelines -> ShowS
Prelude.Show, forall x. Rep ListPipelines x -> ListPipelines
forall x. ListPipelines -> Rep ListPipelines x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPipelines x -> ListPipelines
$cfrom :: forall x. ListPipelines -> Rep ListPipelines x
Prelude.Generic)
newListPipelines ::
ListPipelines
newListPipelines :: ListPipelines
newListPipelines =
ListPipelines'
{ $sel:maxResults:ListPipelines' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListPipelines' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
}
listPipelines_maxResults :: Lens.Lens' ListPipelines (Prelude.Maybe Prelude.Natural)
listPipelines_maxResults :: Lens' ListPipelines (Maybe Natural)
listPipelines_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelines' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPipelines' :: ListPipelines -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPipelines
s@ListPipelines' {} Maybe Natural
a -> ListPipelines
s {$sel:maxResults:ListPipelines' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPipelines)
listPipelines_nextToken :: Lens.Lens' ListPipelines (Prelude.Maybe Prelude.Text)
listPipelines_nextToken :: Lens' ListPipelines (Maybe Text)
listPipelines_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelines' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPipelines' :: ListPipelines -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPipelines
s@ListPipelines' {} Maybe Text
a -> ListPipelines
s {$sel:nextToken:ListPipelines' :: Maybe Text
nextToken = Maybe Text
a} :: ListPipelines)
instance Core.AWSPager ListPipelines where
page :: ListPipelines -> AWSResponse ListPipelines -> Maybe ListPipelines
page ListPipelines
rq AWSResponse ListPipelines
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListPipelines
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPipelinesResponse (Maybe Text)
listPipelinesResponse_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 ListPipelines
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPipelinesResponse (Maybe [PipelineSummary])
listPipelinesResponse_pipelines
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
| Bool
Prelude.otherwise =
forall a. a -> Maybe a
Prelude.Just
forall a b. (a -> b) -> a -> b
Prelude.$ ListPipelines
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListPipelines (Maybe Text)
listPipelines_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListPipelines
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPipelinesResponse (Maybe Text)
listPipelinesResponse_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 ListPipelines where
type
AWSResponse ListPipelines =
ListPipelinesResponse
request :: (Service -> Service) -> ListPipelines -> Request ListPipelines
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 ListPipelines
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListPipelines)))
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 [PipelineSummary] -> Int -> ListPipelinesResponse
ListPipelinesResponse'
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
"pipelines" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
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 ListPipelines where
hashWithSalt :: Int -> ListPipelines -> Int
hashWithSalt Int
_salt ListPipelines' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListPipelines' :: ListPipelines -> Maybe Text
$sel:maxResults:ListPipelines' :: ListPipelines -> 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
instance Prelude.NFData ListPipelines where
rnf :: ListPipelines -> ()
rnf ListPipelines' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListPipelines' :: ListPipelines -> Maybe Text
$sel:maxResults:ListPipelines' :: ListPipelines -> 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
instance Data.ToHeaders ListPipelines where
toHeaders :: ListPipelines -> 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
"CodePipeline_20150709.ListPipelines" ::
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 ListPipelines where
toJSON :: ListPipelines -> Value
toJSON ListPipelines' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListPipelines' :: ListPipelines -> Maybe Text
$sel:maxResults:ListPipelines' :: ListPipelines -> 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
]
)
instance Data.ToPath ListPipelines where
toPath :: ListPipelines -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListPipelines where
toQuery :: ListPipelines -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListPipelinesResponse = ListPipelinesResponse'
{
ListPipelinesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListPipelinesResponse -> Maybe [PipelineSummary]
pipelines :: Prelude.Maybe [PipelineSummary],
ListPipelinesResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListPipelinesResponse -> ListPipelinesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPipelinesResponse -> ListPipelinesResponse -> Bool
$c/= :: ListPipelinesResponse -> ListPipelinesResponse -> Bool
== :: ListPipelinesResponse -> ListPipelinesResponse -> Bool
$c== :: ListPipelinesResponse -> ListPipelinesResponse -> Bool
Prelude.Eq, ReadPrec [ListPipelinesResponse]
ReadPrec ListPipelinesResponse
Int -> ReadS ListPipelinesResponse
ReadS [ListPipelinesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPipelinesResponse]
$creadListPrec :: ReadPrec [ListPipelinesResponse]
readPrec :: ReadPrec ListPipelinesResponse
$creadPrec :: ReadPrec ListPipelinesResponse
readList :: ReadS [ListPipelinesResponse]
$creadList :: ReadS [ListPipelinesResponse]
readsPrec :: Int -> ReadS ListPipelinesResponse
$creadsPrec :: Int -> ReadS ListPipelinesResponse
Prelude.Read, Int -> ListPipelinesResponse -> ShowS
[ListPipelinesResponse] -> ShowS
ListPipelinesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPipelinesResponse] -> ShowS
$cshowList :: [ListPipelinesResponse] -> ShowS
show :: ListPipelinesResponse -> String
$cshow :: ListPipelinesResponse -> String
showsPrec :: Int -> ListPipelinesResponse -> ShowS
$cshowsPrec :: Int -> ListPipelinesResponse -> ShowS
Prelude.Show, forall x. Rep ListPipelinesResponse x -> ListPipelinesResponse
forall x. ListPipelinesResponse -> Rep ListPipelinesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPipelinesResponse x -> ListPipelinesResponse
$cfrom :: forall x. ListPipelinesResponse -> Rep ListPipelinesResponse x
Prelude.Generic)
newListPipelinesResponse ::
Prelude.Int ->
ListPipelinesResponse
newListPipelinesResponse :: Int -> ListPipelinesResponse
newListPipelinesResponse Int
pHttpStatus_ =
ListPipelinesResponse'
{ $sel:nextToken:ListPipelinesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:pipelines:ListPipelinesResponse' :: Maybe [PipelineSummary]
pipelines = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListPipelinesResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listPipelinesResponse_nextToken :: Lens.Lens' ListPipelinesResponse (Prelude.Maybe Prelude.Text)
listPipelinesResponse_nextToken :: Lens' ListPipelinesResponse (Maybe Text)
listPipelinesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelinesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPipelinesResponse' :: ListPipelinesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPipelinesResponse
s@ListPipelinesResponse' {} Maybe Text
a -> ListPipelinesResponse
s {$sel:nextToken:ListPipelinesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPipelinesResponse)
listPipelinesResponse_pipelines :: Lens.Lens' ListPipelinesResponse (Prelude.Maybe [PipelineSummary])
listPipelinesResponse_pipelines :: Lens' ListPipelinesResponse (Maybe [PipelineSummary])
listPipelinesResponse_pipelines = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelinesResponse' {Maybe [PipelineSummary]
pipelines :: Maybe [PipelineSummary]
$sel:pipelines:ListPipelinesResponse' :: ListPipelinesResponse -> Maybe [PipelineSummary]
pipelines} -> Maybe [PipelineSummary]
pipelines) (\s :: ListPipelinesResponse
s@ListPipelinesResponse' {} Maybe [PipelineSummary]
a -> ListPipelinesResponse
s {$sel:pipelines:ListPipelinesResponse' :: Maybe [PipelineSummary]
pipelines = Maybe [PipelineSummary]
a} :: ListPipelinesResponse) 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
listPipelinesResponse_httpStatus :: Lens.Lens' ListPipelinesResponse Prelude.Int
listPipelinesResponse_httpStatus :: Lens' ListPipelinesResponse Int
listPipelinesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelinesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPipelinesResponse' :: ListPipelinesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPipelinesResponse
s@ListPipelinesResponse' {} Int
a -> ListPipelinesResponse
s {$sel:httpStatus:ListPipelinesResponse' :: Int
httpStatus = Int
a} :: ListPipelinesResponse)
instance Prelude.NFData ListPipelinesResponse where
rnf :: ListPipelinesResponse -> ()
rnf ListPipelinesResponse' {Int
Maybe [PipelineSummary]
Maybe Text
httpStatus :: Int
pipelines :: Maybe [PipelineSummary]
nextToken :: Maybe Text
$sel:httpStatus:ListPipelinesResponse' :: ListPipelinesResponse -> Int
$sel:pipelines:ListPipelinesResponse' :: ListPipelinesResponse -> Maybe [PipelineSummary]
$sel:nextToken:ListPipelinesResponse' :: ListPipelinesResponse -> 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 [PipelineSummary]
pipelines
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus