{-# 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.MediaLive.ListInputDevices
(
ListInputDevices (..),
newListInputDevices,
listInputDevices_maxResults,
listInputDevices_nextToken,
ListInputDevicesResponse (..),
newListInputDevicesResponse,
listInputDevicesResponse_inputDevices,
listInputDevicesResponse_nextToken,
listInputDevicesResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaLive.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data ListInputDevices = ListInputDevices'
{ ListInputDevices -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
ListInputDevices -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
}
deriving (ListInputDevices -> ListInputDevices -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListInputDevices -> ListInputDevices -> Bool
$c/= :: ListInputDevices -> ListInputDevices -> Bool
== :: ListInputDevices -> ListInputDevices -> Bool
$c== :: ListInputDevices -> ListInputDevices -> Bool
Prelude.Eq, ReadPrec [ListInputDevices]
ReadPrec ListInputDevices
Int -> ReadS ListInputDevices
ReadS [ListInputDevices]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListInputDevices]
$creadListPrec :: ReadPrec [ListInputDevices]
readPrec :: ReadPrec ListInputDevices
$creadPrec :: ReadPrec ListInputDevices
readList :: ReadS [ListInputDevices]
$creadList :: ReadS [ListInputDevices]
readsPrec :: Int -> ReadS ListInputDevices
$creadsPrec :: Int -> ReadS ListInputDevices
Prelude.Read, Int -> ListInputDevices -> ShowS
[ListInputDevices] -> ShowS
ListInputDevices -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListInputDevices] -> ShowS
$cshowList :: [ListInputDevices] -> ShowS
show :: ListInputDevices -> String
$cshow :: ListInputDevices -> String
showsPrec :: Int -> ListInputDevices -> ShowS
$cshowsPrec :: Int -> ListInputDevices -> ShowS
Prelude.Show, forall x. Rep ListInputDevices x -> ListInputDevices
forall x. ListInputDevices -> Rep ListInputDevices x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListInputDevices x -> ListInputDevices
$cfrom :: forall x. ListInputDevices -> Rep ListInputDevices x
Prelude.Generic)
newListInputDevices ::
ListInputDevices
newListInputDevices :: ListInputDevices
newListInputDevices =
ListInputDevices'
{ $sel:maxResults:ListInputDevices' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListInputDevices' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
}
listInputDevices_maxResults :: Lens.Lens' ListInputDevices (Prelude.Maybe Prelude.Natural)
listInputDevices_maxResults :: Lens' ListInputDevices (Maybe Natural)
listInputDevices_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInputDevices' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListInputDevices' :: ListInputDevices -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListInputDevices
s@ListInputDevices' {} Maybe Natural
a -> ListInputDevices
s {$sel:maxResults:ListInputDevices' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListInputDevices)
listInputDevices_nextToken :: Lens.Lens' ListInputDevices (Prelude.Maybe Prelude.Text)
listInputDevices_nextToken :: Lens' ListInputDevices (Maybe Text)
listInputDevices_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInputDevices' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListInputDevices' :: ListInputDevices -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListInputDevices
s@ListInputDevices' {} Maybe Text
a -> ListInputDevices
s {$sel:nextToken:ListInputDevices' :: Maybe Text
nextToken = Maybe Text
a} :: ListInputDevices)
instance Core.AWSPager ListInputDevices where
page :: ListInputDevices
-> AWSResponse ListInputDevices -> Maybe ListInputDevices
page ListInputDevices
rq AWSResponse ListInputDevices
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListInputDevices
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInputDevicesResponse (Maybe Text)
listInputDevicesResponse_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 ListInputDevices
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInputDevicesResponse (Maybe [InputDeviceSummary])
listInputDevicesResponse_inputDevices
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.$ ListInputDevices
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListInputDevices (Maybe Text)
listInputDevices_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListInputDevices
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInputDevicesResponse (Maybe Text)
listInputDevicesResponse_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 ListInputDevices where
type
AWSResponse ListInputDevices =
ListInputDevicesResponse
request :: (Service -> Service)
-> ListInputDevices -> Request ListInputDevices
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 ListInputDevices
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListInputDevices)))
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 [InputDeviceSummary]
-> Maybe Text -> Int -> ListInputDevicesResponse
ListInputDevicesResponse'
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
"inputDevices" 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 ListInputDevices where
hashWithSalt :: Int -> ListInputDevices -> Int
hashWithSalt Int
_salt ListInputDevices' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListInputDevices' :: ListInputDevices -> Maybe Text
$sel:maxResults:ListInputDevices' :: ListInputDevices -> 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 ListInputDevices where
rnf :: ListInputDevices -> ()
rnf ListInputDevices' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListInputDevices' :: ListInputDevices -> Maybe Text
$sel:maxResults:ListInputDevices' :: ListInputDevices -> 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 ListInputDevices where
toHeaders :: ListInputDevices -> 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 ListInputDevices where
toPath :: ListInputDevices -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/prod/inputDevices"
instance Data.ToQuery ListInputDevices where
toQuery :: ListInputDevices -> QueryString
toQuery ListInputDevices' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListInputDevices' :: ListInputDevices -> Maybe Text
$sel:maxResults:ListInputDevices' :: ListInputDevices -> Maybe Natural
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ 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
]
data ListInputDevicesResponse = ListInputDevicesResponse'
{
ListInputDevicesResponse -> Maybe [InputDeviceSummary]
inputDevices :: Prelude.Maybe [InputDeviceSummary],
ListInputDevicesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListInputDevicesResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListInputDevicesResponse -> ListInputDevicesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListInputDevicesResponse -> ListInputDevicesResponse -> Bool
$c/= :: ListInputDevicesResponse -> ListInputDevicesResponse -> Bool
== :: ListInputDevicesResponse -> ListInputDevicesResponse -> Bool
$c== :: ListInputDevicesResponse -> ListInputDevicesResponse -> Bool
Prelude.Eq, ReadPrec [ListInputDevicesResponse]
ReadPrec ListInputDevicesResponse
Int -> ReadS ListInputDevicesResponse
ReadS [ListInputDevicesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListInputDevicesResponse]
$creadListPrec :: ReadPrec [ListInputDevicesResponse]
readPrec :: ReadPrec ListInputDevicesResponse
$creadPrec :: ReadPrec ListInputDevicesResponse
readList :: ReadS [ListInputDevicesResponse]
$creadList :: ReadS [ListInputDevicesResponse]
readsPrec :: Int -> ReadS ListInputDevicesResponse
$creadsPrec :: Int -> ReadS ListInputDevicesResponse
Prelude.Read, Int -> ListInputDevicesResponse -> ShowS
[ListInputDevicesResponse] -> ShowS
ListInputDevicesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListInputDevicesResponse] -> ShowS
$cshowList :: [ListInputDevicesResponse] -> ShowS
show :: ListInputDevicesResponse -> String
$cshow :: ListInputDevicesResponse -> String
showsPrec :: Int -> ListInputDevicesResponse -> ShowS
$cshowsPrec :: Int -> ListInputDevicesResponse -> ShowS
Prelude.Show, forall x.
Rep ListInputDevicesResponse x -> ListInputDevicesResponse
forall x.
ListInputDevicesResponse -> Rep ListInputDevicesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListInputDevicesResponse x -> ListInputDevicesResponse
$cfrom :: forall x.
ListInputDevicesResponse -> Rep ListInputDevicesResponse x
Prelude.Generic)
newListInputDevicesResponse ::
Prelude.Int ->
ListInputDevicesResponse
newListInputDevicesResponse :: Int -> ListInputDevicesResponse
newListInputDevicesResponse Int
pHttpStatus_ =
ListInputDevicesResponse'
{ $sel:inputDevices:ListInputDevicesResponse' :: Maybe [InputDeviceSummary]
inputDevices =
forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListInputDevicesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListInputDevicesResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listInputDevicesResponse_inputDevices :: Lens.Lens' ListInputDevicesResponse (Prelude.Maybe [InputDeviceSummary])
listInputDevicesResponse_inputDevices :: Lens' ListInputDevicesResponse (Maybe [InputDeviceSummary])
listInputDevicesResponse_inputDevices = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInputDevicesResponse' {Maybe [InputDeviceSummary]
inputDevices :: Maybe [InputDeviceSummary]
$sel:inputDevices:ListInputDevicesResponse' :: ListInputDevicesResponse -> Maybe [InputDeviceSummary]
inputDevices} -> Maybe [InputDeviceSummary]
inputDevices) (\s :: ListInputDevicesResponse
s@ListInputDevicesResponse' {} Maybe [InputDeviceSummary]
a -> ListInputDevicesResponse
s {$sel:inputDevices:ListInputDevicesResponse' :: Maybe [InputDeviceSummary]
inputDevices = Maybe [InputDeviceSummary]
a} :: ListInputDevicesResponse) 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
listInputDevicesResponse_nextToken :: Lens.Lens' ListInputDevicesResponse (Prelude.Maybe Prelude.Text)
listInputDevicesResponse_nextToken :: Lens' ListInputDevicesResponse (Maybe Text)
listInputDevicesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInputDevicesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListInputDevicesResponse' :: ListInputDevicesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListInputDevicesResponse
s@ListInputDevicesResponse' {} Maybe Text
a -> ListInputDevicesResponse
s {$sel:nextToken:ListInputDevicesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListInputDevicesResponse)
listInputDevicesResponse_httpStatus :: Lens.Lens' ListInputDevicesResponse Prelude.Int
listInputDevicesResponse_httpStatus :: Lens' ListInputDevicesResponse Int
listInputDevicesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInputDevicesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListInputDevicesResponse' :: ListInputDevicesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListInputDevicesResponse
s@ListInputDevicesResponse' {} Int
a -> ListInputDevicesResponse
s {$sel:httpStatus:ListInputDevicesResponse' :: Int
httpStatus = Int
a} :: ListInputDevicesResponse)
instance Prelude.NFData ListInputDevicesResponse where
rnf :: ListInputDevicesResponse -> ()
rnf ListInputDevicesResponse' {Int
Maybe [InputDeviceSummary]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
inputDevices :: Maybe [InputDeviceSummary]
$sel:httpStatus:ListInputDevicesResponse' :: ListInputDevicesResponse -> Int
$sel:nextToken:ListInputDevicesResponse' :: ListInputDevicesResponse -> Maybe Text
$sel:inputDevices:ListInputDevicesResponse' :: ListInputDevicesResponse -> Maybe [InputDeviceSummary]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [InputDeviceSummary]
inputDevices
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