{-# 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.DeviceFarm.ListArtifacts
(
ListArtifacts (..),
newListArtifacts,
listArtifacts_nextToken,
listArtifacts_arn,
listArtifacts_type,
ListArtifactsResponse (..),
newListArtifactsResponse,
listArtifactsResponse_artifacts,
listArtifactsResponse_nextToken,
listArtifactsResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DeviceFarm.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data ListArtifacts = ListArtifacts'
{
ListArtifacts -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListArtifacts -> Text
arn :: Prelude.Text,
ListArtifacts -> ArtifactCategory
type' :: ArtifactCategory
}
deriving (ListArtifacts -> ListArtifacts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListArtifacts -> ListArtifacts -> Bool
$c/= :: ListArtifacts -> ListArtifacts -> Bool
== :: ListArtifacts -> ListArtifacts -> Bool
$c== :: ListArtifacts -> ListArtifacts -> Bool
Prelude.Eq, ReadPrec [ListArtifacts]
ReadPrec ListArtifacts
Int -> ReadS ListArtifacts
ReadS [ListArtifacts]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListArtifacts]
$creadListPrec :: ReadPrec [ListArtifacts]
readPrec :: ReadPrec ListArtifacts
$creadPrec :: ReadPrec ListArtifacts
readList :: ReadS [ListArtifacts]
$creadList :: ReadS [ListArtifacts]
readsPrec :: Int -> ReadS ListArtifacts
$creadsPrec :: Int -> ReadS ListArtifacts
Prelude.Read, Int -> ListArtifacts -> ShowS
[ListArtifacts] -> ShowS
ListArtifacts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListArtifacts] -> ShowS
$cshowList :: [ListArtifacts] -> ShowS
show :: ListArtifacts -> String
$cshow :: ListArtifacts -> String
showsPrec :: Int -> ListArtifacts -> ShowS
$cshowsPrec :: Int -> ListArtifacts -> ShowS
Prelude.Show, forall x. Rep ListArtifacts x -> ListArtifacts
forall x. ListArtifacts -> Rep ListArtifacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListArtifacts x -> ListArtifacts
$cfrom :: forall x. ListArtifacts -> Rep ListArtifacts x
Prelude.Generic)
newListArtifacts ::
Prelude.Text ->
ArtifactCategory ->
ListArtifacts
newListArtifacts :: Text -> ArtifactCategory -> ListArtifacts
newListArtifacts Text
pArn_ ArtifactCategory
pType_ =
ListArtifacts'
{ $sel:nextToken:ListArtifacts' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:arn:ListArtifacts' :: Text
arn = Text
pArn_,
$sel:type':ListArtifacts' :: ArtifactCategory
type' = ArtifactCategory
pType_
}
listArtifacts_nextToken :: Lens.Lens' ListArtifacts (Prelude.Maybe Prelude.Text)
listArtifacts_nextToken :: Lens' ListArtifacts (Maybe Text)
listArtifacts_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArtifacts' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListArtifacts' :: ListArtifacts -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListArtifacts
s@ListArtifacts' {} Maybe Text
a -> ListArtifacts
s {$sel:nextToken:ListArtifacts' :: Maybe Text
nextToken = Maybe Text
a} :: ListArtifacts)
listArtifacts_arn :: Lens.Lens' ListArtifacts Prelude.Text
listArtifacts_arn :: Lens' ListArtifacts Text
listArtifacts_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArtifacts' {Text
arn :: Text
$sel:arn:ListArtifacts' :: ListArtifacts -> Text
arn} -> Text
arn) (\s :: ListArtifacts
s@ListArtifacts' {} Text
a -> ListArtifacts
s {$sel:arn:ListArtifacts' :: Text
arn = Text
a} :: ListArtifacts)
listArtifacts_type :: Lens.Lens' ListArtifacts ArtifactCategory
listArtifacts_type :: Lens' ListArtifacts ArtifactCategory
listArtifacts_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArtifacts' {ArtifactCategory
type' :: ArtifactCategory
$sel:type':ListArtifacts' :: ListArtifacts -> ArtifactCategory
type'} -> ArtifactCategory
type') (\s :: ListArtifacts
s@ListArtifacts' {} ArtifactCategory
a -> ListArtifacts
s {$sel:type':ListArtifacts' :: ArtifactCategory
type' = ArtifactCategory
a} :: ListArtifacts)
instance Core.AWSPager ListArtifacts where
page :: ListArtifacts -> AWSResponse ListArtifacts -> Maybe ListArtifacts
page ListArtifacts
rq AWSResponse ListArtifacts
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListArtifacts
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListArtifactsResponse (Maybe Text)
listArtifactsResponse_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 ListArtifacts
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListArtifactsResponse (Maybe [Artifact])
listArtifactsResponse_artifacts
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.$ ListArtifacts
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListArtifacts (Maybe Text)
listArtifacts_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListArtifacts
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListArtifactsResponse (Maybe Text)
listArtifactsResponse_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 ListArtifacts where
type
AWSResponse ListArtifacts =
ListArtifactsResponse
request :: (Service -> Service) -> ListArtifacts -> Request ListArtifacts
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 ListArtifacts
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListArtifacts)))
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 [Artifact] -> Maybe Text -> Int -> ListArtifactsResponse
ListArtifactsResponse'
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
"artifacts" 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.<*> (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))
)
instance Prelude.Hashable ListArtifacts where
hashWithSalt :: Int -> ListArtifacts -> Int
hashWithSalt Int
_salt ListArtifacts' {Maybe Text
Text
ArtifactCategory
type' :: ArtifactCategory
arn :: Text
nextToken :: Maybe Text
$sel:type':ListArtifacts' :: ListArtifacts -> ArtifactCategory
$sel:arn:ListArtifacts' :: ListArtifacts -> Text
$sel:nextToken:ListArtifacts' :: ListArtifacts -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ArtifactCategory
type'
instance Prelude.NFData ListArtifacts where
rnf :: ListArtifacts -> ()
rnf ListArtifacts' {Maybe Text
Text
ArtifactCategory
type' :: ArtifactCategory
arn :: Text
nextToken :: Maybe Text
$sel:type':ListArtifacts' :: ListArtifacts -> ArtifactCategory
$sel:arn:ListArtifacts' :: ListArtifacts -> Text
$sel:nextToken:ListArtifacts' :: ListArtifacts -> 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 Text
arn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ArtifactCategory
type'
instance Data.ToHeaders ListArtifacts where
toHeaders :: ListArtifacts -> 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
"DeviceFarm_20150623.ListArtifacts" ::
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 ListArtifacts where
toJSON :: ListArtifacts -> Value
toJSON ListArtifacts' {Maybe Text
Text
ArtifactCategory
type' :: ArtifactCategory
arn :: Text
nextToken :: Maybe Text
$sel:type':ListArtifacts' :: ListArtifacts -> ArtifactCategory
$sel:arn:ListArtifacts' :: ListArtifacts -> Text
$sel:nextToken:ListArtifacts' :: ListArtifacts -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (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,
forall a. a -> Maybe a
Prelude.Just (Key
"arn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
arn),
forall a. a -> Maybe a
Prelude.Just (Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ArtifactCategory
type')
]
)
instance Data.ToPath ListArtifacts where
toPath :: ListArtifacts -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListArtifacts where
toQuery :: ListArtifacts -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListArtifactsResponse = ListArtifactsResponse'
{
ListArtifactsResponse -> Maybe [Artifact]
artifacts :: Prelude.Maybe [Artifact],
ListArtifactsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListArtifactsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListArtifactsResponse -> ListArtifactsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListArtifactsResponse -> ListArtifactsResponse -> Bool
$c/= :: ListArtifactsResponse -> ListArtifactsResponse -> Bool
== :: ListArtifactsResponse -> ListArtifactsResponse -> Bool
$c== :: ListArtifactsResponse -> ListArtifactsResponse -> Bool
Prelude.Eq, ReadPrec [ListArtifactsResponse]
ReadPrec ListArtifactsResponse
Int -> ReadS ListArtifactsResponse
ReadS [ListArtifactsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListArtifactsResponse]
$creadListPrec :: ReadPrec [ListArtifactsResponse]
readPrec :: ReadPrec ListArtifactsResponse
$creadPrec :: ReadPrec ListArtifactsResponse
readList :: ReadS [ListArtifactsResponse]
$creadList :: ReadS [ListArtifactsResponse]
readsPrec :: Int -> ReadS ListArtifactsResponse
$creadsPrec :: Int -> ReadS ListArtifactsResponse
Prelude.Read, Int -> ListArtifactsResponse -> ShowS
[ListArtifactsResponse] -> ShowS
ListArtifactsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListArtifactsResponse] -> ShowS
$cshowList :: [ListArtifactsResponse] -> ShowS
show :: ListArtifactsResponse -> String
$cshow :: ListArtifactsResponse -> String
showsPrec :: Int -> ListArtifactsResponse -> ShowS
$cshowsPrec :: Int -> ListArtifactsResponse -> ShowS
Prelude.Show, forall x. Rep ListArtifactsResponse x -> ListArtifactsResponse
forall x. ListArtifactsResponse -> Rep ListArtifactsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListArtifactsResponse x -> ListArtifactsResponse
$cfrom :: forall x. ListArtifactsResponse -> Rep ListArtifactsResponse x
Prelude.Generic)
newListArtifactsResponse ::
Prelude.Int ->
ListArtifactsResponse
newListArtifactsResponse :: Int -> ListArtifactsResponse
newListArtifactsResponse Int
pHttpStatus_ =
ListArtifactsResponse'
{ $sel:artifacts:ListArtifactsResponse' :: Maybe [Artifact]
artifacts = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListArtifactsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListArtifactsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listArtifactsResponse_artifacts :: Lens.Lens' ListArtifactsResponse (Prelude.Maybe [Artifact])
listArtifactsResponse_artifacts :: Lens' ListArtifactsResponse (Maybe [Artifact])
listArtifactsResponse_artifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArtifactsResponse' {Maybe [Artifact]
artifacts :: Maybe [Artifact]
$sel:artifacts:ListArtifactsResponse' :: ListArtifactsResponse -> Maybe [Artifact]
artifacts} -> Maybe [Artifact]
artifacts) (\s :: ListArtifactsResponse
s@ListArtifactsResponse' {} Maybe [Artifact]
a -> ListArtifactsResponse
s {$sel:artifacts:ListArtifactsResponse' :: Maybe [Artifact]
artifacts = Maybe [Artifact]
a} :: ListArtifactsResponse) 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
listArtifactsResponse_nextToken :: Lens.Lens' ListArtifactsResponse (Prelude.Maybe Prelude.Text)
listArtifactsResponse_nextToken :: Lens' ListArtifactsResponse (Maybe Text)
listArtifactsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArtifactsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListArtifactsResponse' :: ListArtifactsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListArtifactsResponse
s@ListArtifactsResponse' {} Maybe Text
a -> ListArtifactsResponse
s {$sel:nextToken:ListArtifactsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListArtifactsResponse)
listArtifactsResponse_httpStatus :: Lens.Lens' ListArtifactsResponse Prelude.Int
listArtifactsResponse_httpStatus :: Lens' ListArtifactsResponse Int
listArtifactsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListArtifactsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListArtifactsResponse' :: ListArtifactsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListArtifactsResponse
s@ListArtifactsResponse' {} Int
a -> ListArtifactsResponse
s {$sel:httpStatus:ListArtifactsResponse' :: Int
httpStatus = Int
a} :: ListArtifactsResponse)
instance Prelude.NFData ListArtifactsResponse where
rnf :: ListArtifactsResponse -> ()
rnf ListArtifactsResponse' {Int
Maybe [Artifact]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
artifacts :: Maybe [Artifact]
$sel:httpStatus:ListArtifactsResponse' :: ListArtifactsResponse -> Int
$sel:nextToken:ListArtifactsResponse' :: ListArtifactsResponse -> Maybe Text
$sel:artifacts:ListArtifactsResponse' :: ListArtifactsResponse -> Maybe [Artifact]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Artifact]
artifacts
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 Int
httpStatus