{-# 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.EMR.ListStudios
(
ListStudios (..),
newListStudios,
listStudios_marker,
ListStudiosResponse (..),
newListStudiosResponse,
listStudiosResponse_marker,
listStudiosResponse_studios,
listStudiosResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EMR.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data ListStudios = ListStudios'
{
ListStudios -> Maybe Text
marker :: Prelude.Maybe Prelude.Text
}
deriving (ListStudios -> ListStudios -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStudios -> ListStudios -> Bool
$c/= :: ListStudios -> ListStudios -> Bool
== :: ListStudios -> ListStudios -> Bool
$c== :: ListStudios -> ListStudios -> Bool
Prelude.Eq, ReadPrec [ListStudios]
ReadPrec ListStudios
Int -> ReadS ListStudios
ReadS [ListStudios]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStudios]
$creadListPrec :: ReadPrec [ListStudios]
readPrec :: ReadPrec ListStudios
$creadPrec :: ReadPrec ListStudios
readList :: ReadS [ListStudios]
$creadList :: ReadS [ListStudios]
readsPrec :: Int -> ReadS ListStudios
$creadsPrec :: Int -> ReadS ListStudios
Prelude.Read, Int -> ListStudios -> ShowS
[ListStudios] -> ShowS
ListStudios -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStudios] -> ShowS
$cshowList :: [ListStudios] -> ShowS
show :: ListStudios -> String
$cshow :: ListStudios -> String
showsPrec :: Int -> ListStudios -> ShowS
$cshowsPrec :: Int -> ListStudios -> ShowS
Prelude.Show, forall x. Rep ListStudios x -> ListStudios
forall x. ListStudios -> Rep ListStudios x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListStudios x -> ListStudios
$cfrom :: forall x. ListStudios -> Rep ListStudios x
Prelude.Generic)
newListStudios ::
ListStudios
newListStudios :: ListStudios
newListStudios =
ListStudios' {$sel:marker:ListStudios' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing}
listStudios_marker :: Lens.Lens' ListStudios (Prelude.Maybe Prelude.Text)
listStudios_marker :: Lens' ListStudios (Maybe Text)
listStudios_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStudios' {Maybe Text
marker :: Maybe Text
$sel:marker:ListStudios' :: ListStudios -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListStudios
s@ListStudios' {} Maybe Text
a -> ListStudios
s {$sel:marker:ListStudios' :: Maybe Text
marker = Maybe Text
a} :: ListStudios)
instance Core.AWSPager ListStudios where
page :: ListStudios -> AWSResponse ListStudios -> Maybe ListStudios
page ListStudios
rq AWSResponse ListStudios
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListStudios
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStudiosResponse (Maybe Text)
listStudiosResponse_marker
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 ListStudios
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStudiosResponse (Maybe [StudioSummary])
listStudiosResponse_studios
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.$ ListStudios
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListStudios (Maybe Text)
listStudios_marker
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListStudios
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStudiosResponse (Maybe Text)
listStudiosResponse_marker
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 ListStudios where
type AWSResponse ListStudios = ListStudiosResponse
request :: (Service -> Service) -> ListStudios -> Request ListStudios
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 ListStudios
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListStudios)))
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 [StudioSummary] -> Int -> ListStudiosResponse
ListStudiosResponse'
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
"Marker")
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
"Studios" 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 ListStudios where
hashWithSalt :: Int -> ListStudios -> Int
hashWithSalt Int
_salt ListStudios' {Maybe Text
marker :: Maybe Text
$sel:marker:ListStudios' :: ListStudios -> Maybe Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
instance Prelude.NFData ListStudios where
rnf :: ListStudios -> ()
rnf ListStudios' {Maybe Text
marker :: Maybe Text
$sel:marker:ListStudios' :: ListStudios -> Maybe Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
instance Data.ToHeaders ListStudios where
toHeaders :: ListStudios -> 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
"ElasticMapReduce.ListStudios" ::
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 ListStudios where
toJSON :: ListStudios -> Value
toJSON ListStudios' {Maybe Text
marker :: Maybe Text
$sel:marker:ListStudios' :: ListStudios -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[(Key
"Marker" 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
marker]
)
instance Data.ToPath ListStudios where
toPath :: ListStudios -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListStudios where
toQuery :: ListStudios -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListStudiosResponse = ListStudiosResponse'
{
ListStudiosResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
ListStudiosResponse -> Maybe [StudioSummary]
studios :: Prelude.Maybe [StudioSummary],
ListStudiosResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListStudiosResponse -> ListStudiosResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStudiosResponse -> ListStudiosResponse -> Bool
$c/= :: ListStudiosResponse -> ListStudiosResponse -> Bool
== :: ListStudiosResponse -> ListStudiosResponse -> Bool
$c== :: ListStudiosResponse -> ListStudiosResponse -> Bool
Prelude.Eq, ReadPrec [ListStudiosResponse]
ReadPrec ListStudiosResponse
Int -> ReadS ListStudiosResponse
ReadS [ListStudiosResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStudiosResponse]
$creadListPrec :: ReadPrec [ListStudiosResponse]
readPrec :: ReadPrec ListStudiosResponse
$creadPrec :: ReadPrec ListStudiosResponse
readList :: ReadS [ListStudiosResponse]
$creadList :: ReadS [ListStudiosResponse]
readsPrec :: Int -> ReadS ListStudiosResponse
$creadsPrec :: Int -> ReadS ListStudiosResponse
Prelude.Read, Int -> ListStudiosResponse -> ShowS
[ListStudiosResponse] -> ShowS
ListStudiosResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStudiosResponse] -> ShowS
$cshowList :: [ListStudiosResponse] -> ShowS
show :: ListStudiosResponse -> String
$cshow :: ListStudiosResponse -> String
showsPrec :: Int -> ListStudiosResponse -> ShowS
$cshowsPrec :: Int -> ListStudiosResponse -> ShowS
Prelude.Show, forall x. Rep ListStudiosResponse x -> ListStudiosResponse
forall x. ListStudiosResponse -> Rep ListStudiosResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListStudiosResponse x -> ListStudiosResponse
$cfrom :: forall x. ListStudiosResponse -> Rep ListStudiosResponse x
Prelude.Generic)
newListStudiosResponse ::
Prelude.Int ->
ListStudiosResponse
newListStudiosResponse :: Int -> ListStudiosResponse
newListStudiosResponse Int
pHttpStatus_ =
ListStudiosResponse'
{ $sel:marker:ListStudiosResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
$sel:studios:ListStudiosResponse' :: Maybe [StudioSummary]
studios = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListStudiosResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listStudiosResponse_marker :: Lens.Lens' ListStudiosResponse (Prelude.Maybe Prelude.Text)
listStudiosResponse_marker :: Lens' ListStudiosResponse (Maybe Text)
listStudiosResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStudiosResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:ListStudiosResponse' :: ListStudiosResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListStudiosResponse
s@ListStudiosResponse' {} Maybe Text
a -> ListStudiosResponse
s {$sel:marker:ListStudiosResponse' :: Maybe Text
marker = Maybe Text
a} :: ListStudiosResponse)
listStudiosResponse_studios :: Lens.Lens' ListStudiosResponse (Prelude.Maybe [StudioSummary])
listStudiosResponse_studios :: Lens' ListStudiosResponse (Maybe [StudioSummary])
listStudiosResponse_studios = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStudiosResponse' {Maybe [StudioSummary]
studios :: Maybe [StudioSummary]
$sel:studios:ListStudiosResponse' :: ListStudiosResponse -> Maybe [StudioSummary]
studios} -> Maybe [StudioSummary]
studios) (\s :: ListStudiosResponse
s@ListStudiosResponse' {} Maybe [StudioSummary]
a -> ListStudiosResponse
s {$sel:studios:ListStudiosResponse' :: Maybe [StudioSummary]
studios = Maybe [StudioSummary]
a} :: ListStudiosResponse) 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
listStudiosResponse_httpStatus :: Lens.Lens' ListStudiosResponse Prelude.Int
listStudiosResponse_httpStatus :: Lens' ListStudiosResponse Int
listStudiosResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStudiosResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListStudiosResponse' :: ListStudiosResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListStudiosResponse
s@ListStudiosResponse' {} Int
a -> ListStudiosResponse
s {$sel:httpStatus:ListStudiosResponse' :: Int
httpStatus = Int
a} :: ListStudiosResponse)
instance Prelude.NFData ListStudiosResponse where
rnf :: ListStudiosResponse -> ()
rnf ListStudiosResponse' {Int
Maybe [StudioSummary]
Maybe Text
httpStatus :: Int
studios :: Maybe [StudioSummary]
marker :: Maybe Text
$sel:httpStatus:ListStudiosResponse' :: ListStudiosResponse -> Int
$sel:studios:ListStudiosResponse' :: ListStudiosResponse -> Maybe [StudioSummary]
$sel:marker:ListStudiosResponse' :: ListStudiosResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [StudioSummary]
studios
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus