{-# 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.Location.AssociateTrackerConsumer
(
AssociateTrackerConsumer (..),
newAssociateTrackerConsumer,
associateTrackerConsumer_consumerArn,
associateTrackerConsumer_trackerName,
AssociateTrackerConsumerResponse (..),
newAssociateTrackerConsumerResponse,
associateTrackerConsumerResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Location.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data AssociateTrackerConsumer = AssociateTrackerConsumer'
{
AssociateTrackerConsumer -> Text
consumerArn :: Prelude.Text,
AssociateTrackerConsumer -> Text
trackerName :: Prelude.Text
}
deriving (AssociateTrackerConsumer -> AssociateTrackerConsumer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateTrackerConsumer -> AssociateTrackerConsumer -> Bool
$c/= :: AssociateTrackerConsumer -> AssociateTrackerConsumer -> Bool
== :: AssociateTrackerConsumer -> AssociateTrackerConsumer -> Bool
$c== :: AssociateTrackerConsumer -> AssociateTrackerConsumer -> Bool
Prelude.Eq, ReadPrec [AssociateTrackerConsumer]
ReadPrec AssociateTrackerConsumer
Int -> ReadS AssociateTrackerConsumer
ReadS [AssociateTrackerConsumer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateTrackerConsumer]
$creadListPrec :: ReadPrec [AssociateTrackerConsumer]
readPrec :: ReadPrec AssociateTrackerConsumer
$creadPrec :: ReadPrec AssociateTrackerConsumer
readList :: ReadS [AssociateTrackerConsumer]
$creadList :: ReadS [AssociateTrackerConsumer]
readsPrec :: Int -> ReadS AssociateTrackerConsumer
$creadsPrec :: Int -> ReadS AssociateTrackerConsumer
Prelude.Read, Int -> AssociateTrackerConsumer -> ShowS
[AssociateTrackerConsumer] -> ShowS
AssociateTrackerConsumer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateTrackerConsumer] -> ShowS
$cshowList :: [AssociateTrackerConsumer] -> ShowS
show :: AssociateTrackerConsumer -> String
$cshow :: AssociateTrackerConsumer -> String
showsPrec :: Int -> AssociateTrackerConsumer -> ShowS
$cshowsPrec :: Int -> AssociateTrackerConsumer -> ShowS
Prelude.Show, forall x.
Rep AssociateTrackerConsumer x -> AssociateTrackerConsumer
forall x.
AssociateTrackerConsumer -> Rep AssociateTrackerConsumer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateTrackerConsumer x -> AssociateTrackerConsumer
$cfrom :: forall x.
AssociateTrackerConsumer -> Rep AssociateTrackerConsumer x
Prelude.Generic)
newAssociateTrackerConsumer ::
Prelude.Text ->
Prelude.Text ->
AssociateTrackerConsumer
newAssociateTrackerConsumer :: Text -> Text -> AssociateTrackerConsumer
newAssociateTrackerConsumer
Text
pConsumerArn_
Text
pTrackerName_ =
AssociateTrackerConsumer'
{ $sel:consumerArn:AssociateTrackerConsumer' :: Text
consumerArn =
Text
pConsumerArn_,
$sel:trackerName:AssociateTrackerConsumer' :: Text
trackerName = Text
pTrackerName_
}
associateTrackerConsumer_consumerArn :: Lens.Lens' AssociateTrackerConsumer Prelude.Text
associateTrackerConsumer_consumerArn :: Lens' AssociateTrackerConsumer Text
associateTrackerConsumer_consumerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateTrackerConsumer' {Text
consumerArn :: Text
$sel:consumerArn:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
consumerArn} -> Text
consumerArn) (\s :: AssociateTrackerConsumer
s@AssociateTrackerConsumer' {} Text
a -> AssociateTrackerConsumer
s {$sel:consumerArn:AssociateTrackerConsumer' :: Text
consumerArn = Text
a} :: AssociateTrackerConsumer)
associateTrackerConsumer_trackerName :: Lens.Lens' AssociateTrackerConsumer Prelude.Text
associateTrackerConsumer_trackerName :: Lens' AssociateTrackerConsumer Text
associateTrackerConsumer_trackerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateTrackerConsumer' {Text
trackerName :: Text
$sel:trackerName:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
trackerName} -> Text
trackerName) (\s :: AssociateTrackerConsumer
s@AssociateTrackerConsumer' {} Text
a -> AssociateTrackerConsumer
s {$sel:trackerName:AssociateTrackerConsumer' :: Text
trackerName = Text
a} :: AssociateTrackerConsumer)
instance Core.AWSRequest AssociateTrackerConsumer where
type
AWSResponse AssociateTrackerConsumer =
AssociateTrackerConsumerResponse
request :: (Service -> Service)
-> AssociateTrackerConsumer -> Request AssociateTrackerConsumer
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 AssociateTrackerConsumer
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse AssociateTrackerConsumer)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
( \Int
s ResponseHeaders
h ()
x ->
Int -> AssociateTrackerConsumerResponse
AssociateTrackerConsumerResponse'
forall (f :: * -> *) a b. Functor 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 AssociateTrackerConsumer where
hashWithSalt :: Int -> AssociateTrackerConsumer -> Int
hashWithSalt Int
_salt AssociateTrackerConsumer' {Text
trackerName :: Text
consumerArn :: Text
$sel:trackerName:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
$sel:consumerArn:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
consumerArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
trackerName
instance Prelude.NFData AssociateTrackerConsumer where
rnf :: AssociateTrackerConsumer -> ()
rnf AssociateTrackerConsumer' {Text
trackerName :: Text
consumerArn :: Text
$sel:trackerName:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
$sel:consumerArn:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
consumerArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
trackerName
instance Data.ToHeaders AssociateTrackerConsumer where
toHeaders :: AssociateTrackerConsumer -> 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.ToJSON AssociateTrackerConsumer where
toJSON :: AssociateTrackerConsumer -> Value
toJSON AssociateTrackerConsumer' {Text
trackerName :: Text
consumerArn :: Text
$sel:trackerName:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
$sel:consumerArn:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[forall a. a -> Maybe a
Prelude.Just (Key
"ConsumerArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
consumerArn)]
)
instance Data.ToPath AssociateTrackerConsumer where
toPath :: AssociateTrackerConsumer -> ByteString
toPath AssociateTrackerConsumer' {Text
trackerName :: Text
consumerArn :: Text
$sel:trackerName:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
$sel:consumerArn:AssociateTrackerConsumer' :: AssociateTrackerConsumer -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/tracking/v0/trackers/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
trackerName,
ByteString
"/consumers"
]
instance Data.ToQuery AssociateTrackerConsumer where
toQuery :: AssociateTrackerConsumer -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data AssociateTrackerConsumerResponse = AssociateTrackerConsumerResponse'
{
AssociateTrackerConsumerResponse -> Int
httpStatus :: Prelude.Int
}
deriving (AssociateTrackerConsumerResponse
-> AssociateTrackerConsumerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateTrackerConsumerResponse
-> AssociateTrackerConsumerResponse -> Bool
$c/= :: AssociateTrackerConsumerResponse
-> AssociateTrackerConsumerResponse -> Bool
== :: AssociateTrackerConsumerResponse
-> AssociateTrackerConsumerResponse -> Bool
$c== :: AssociateTrackerConsumerResponse
-> AssociateTrackerConsumerResponse -> Bool
Prelude.Eq, ReadPrec [AssociateTrackerConsumerResponse]
ReadPrec AssociateTrackerConsumerResponse
Int -> ReadS AssociateTrackerConsumerResponse
ReadS [AssociateTrackerConsumerResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateTrackerConsumerResponse]
$creadListPrec :: ReadPrec [AssociateTrackerConsumerResponse]
readPrec :: ReadPrec AssociateTrackerConsumerResponse
$creadPrec :: ReadPrec AssociateTrackerConsumerResponse
readList :: ReadS [AssociateTrackerConsumerResponse]
$creadList :: ReadS [AssociateTrackerConsumerResponse]
readsPrec :: Int -> ReadS AssociateTrackerConsumerResponse
$creadsPrec :: Int -> ReadS AssociateTrackerConsumerResponse
Prelude.Read, Int -> AssociateTrackerConsumerResponse -> ShowS
[AssociateTrackerConsumerResponse] -> ShowS
AssociateTrackerConsumerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateTrackerConsumerResponse] -> ShowS
$cshowList :: [AssociateTrackerConsumerResponse] -> ShowS
show :: AssociateTrackerConsumerResponse -> String
$cshow :: AssociateTrackerConsumerResponse -> String
showsPrec :: Int -> AssociateTrackerConsumerResponse -> ShowS
$cshowsPrec :: Int -> AssociateTrackerConsumerResponse -> ShowS
Prelude.Show, forall x.
Rep AssociateTrackerConsumerResponse x
-> AssociateTrackerConsumerResponse
forall x.
AssociateTrackerConsumerResponse
-> Rep AssociateTrackerConsumerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateTrackerConsumerResponse x
-> AssociateTrackerConsumerResponse
$cfrom :: forall x.
AssociateTrackerConsumerResponse
-> Rep AssociateTrackerConsumerResponse x
Prelude.Generic)
newAssociateTrackerConsumerResponse ::
Prelude.Int ->
AssociateTrackerConsumerResponse
newAssociateTrackerConsumerResponse :: Int -> AssociateTrackerConsumerResponse
newAssociateTrackerConsumerResponse Int
pHttpStatus_ =
AssociateTrackerConsumerResponse'
{ $sel:httpStatus:AssociateTrackerConsumerResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
associateTrackerConsumerResponse_httpStatus :: Lens.Lens' AssociateTrackerConsumerResponse Prelude.Int
associateTrackerConsumerResponse_httpStatus :: Lens' AssociateTrackerConsumerResponse Int
associateTrackerConsumerResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateTrackerConsumerResponse' {Int
httpStatus :: Int
$sel:httpStatus:AssociateTrackerConsumerResponse' :: AssociateTrackerConsumerResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AssociateTrackerConsumerResponse
s@AssociateTrackerConsumerResponse' {} Int
a -> AssociateTrackerConsumerResponse
s {$sel:httpStatus:AssociateTrackerConsumerResponse' :: Int
httpStatus = Int
a} :: AssociateTrackerConsumerResponse)
instance
Prelude.NFData
AssociateTrackerConsumerResponse
where
rnf :: AssociateTrackerConsumerResponse -> ()
rnf AssociateTrackerConsumerResponse' {Int
httpStatus :: Int
$sel:httpStatus:AssociateTrackerConsumerResponse' :: AssociateTrackerConsumerResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus