{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Location.DisassociateTrackerConsumer
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes the association between a tracker resource and a geofence
-- collection.
--
-- Once you unlink a tracker resource from a geofence collection, the
-- tracker positions will no longer be automatically evaluated against
-- geofences.
module Amazonka.Location.DisassociateTrackerConsumer
  ( -- * Creating a Request
    DisassociateTrackerConsumer (..),
    newDisassociateTrackerConsumer,

    -- * Request Lenses
    disassociateTrackerConsumer_consumerArn,
    disassociateTrackerConsumer_trackerName,

    -- * Destructuring the Response
    DisassociateTrackerConsumerResponse (..),
    newDisassociateTrackerConsumerResponse,

    -- * Response Lenses
    disassociateTrackerConsumerResponse_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

-- | /See:/ 'newDisassociateTrackerConsumer' smart constructor.
data DisassociateTrackerConsumer = DisassociateTrackerConsumer'
  { -- | The Amazon Resource Name (ARN) for the geofence collection to be
    -- disassociated from the tracker resource. Used when you need to specify a
    -- resource across all AWS.
    --
    -- -   Format example:
    --     @arn:aws:geo:region:account-id:geofence-collection\/ExampleGeofenceCollectionConsumer@
    DisassociateTrackerConsumer -> Text
consumerArn :: Prelude.Text,
    -- | The name of the tracker resource to be dissociated from the consumer.
    DisassociateTrackerConsumer -> Text
trackerName :: Prelude.Text
  }
  deriving (DisassociateTrackerConsumer -> DisassociateTrackerConsumer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateTrackerConsumer -> DisassociateTrackerConsumer -> Bool
$c/= :: DisassociateTrackerConsumer -> DisassociateTrackerConsumer -> Bool
== :: DisassociateTrackerConsumer -> DisassociateTrackerConsumer -> Bool
$c== :: DisassociateTrackerConsumer -> DisassociateTrackerConsumer -> Bool
Prelude.Eq, ReadPrec [DisassociateTrackerConsumer]
ReadPrec DisassociateTrackerConsumer
Int -> ReadS DisassociateTrackerConsumer
ReadS [DisassociateTrackerConsumer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateTrackerConsumer]
$creadListPrec :: ReadPrec [DisassociateTrackerConsumer]
readPrec :: ReadPrec DisassociateTrackerConsumer
$creadPrec :: ReadPrec DisassociateTrackerConsumer
readList :: ReadS [DisassociateTrackerConsumer]
$creadList :: ReadS [DisassociateTrackerConsumer]
readsPrec :: Int -> ReadS DisassociateTrackerConsumer
$creadsPrec :: Int -> ReadS DisassociateTrackerConsumer
Prelude.Read, Int -> DisassociateTrackerConsumer -> ShowS
[DisassociateTrackerConsumer] -> ShowS
DisassociateTrackerConsumer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateTrackerConsumer] -> ShowS
$cshowList :: [DisassociateTrackerConsumer] -> ShowS
show :: DisassociateTrackerConsumer -> String
$cshow :: DisassociateTrackerConsumer -> String
showsPrec :: Int -> DisassociateTrackerConsumer -> ShowS
$cshowsPrec :: Int -> DisassociateTrackerConsumer -> ShowS
Prelude.Show, forall x.
Rep DisassociateTrackerConsumer x -> DisassociateTrackerConsumer
forall x.
DisassociateTrackerConsumer -> Rep DisassociateTrackerConsumer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateTrackerConsumer x -> DisassociateTrackerConsumer
$cfrom :: forall x.
DisassociateTrackerConsumer -> Rep DisassociateTrackerConsumer x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateTrackerConsumer' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'consumerArn', 'disassociateTrackerConsumer_consumerArn' - The Amazon Resource Name (ARN) for the geofence collection to be
-- disassociated from the tracker resource. Used when you need to specify a
-- resource across all AWS.
--
-- -   Format example:
--     @arn:aws:geo:region:account-id:geofence-collection\/ExampleGeofenceCollectionConsumer@
--
-- 'trackerName', 'disassociateTrackerConsumer_trackerName' - The name of the tracker resource to be dissociated from the consumer.
newDisassociateTrackerConsumer ::
  -- | 'consumerArn'
  Prelude.Text ->
  -- | 'trackerName'
  Prelude.Text ->
  DisassociateTrackerConsumer
newDisassociateTrackerConsumer :: Text -> Text -> DisassociateTrackerConsumer
newDisassociateTrackerConsumer
  Text
pConsumerArn_
  Text
pTrackerName_ =
    DisassociateTrackerConsumer'
      { $sel:consumerArn:DisassociateTrackerConsumer' :: Text
consumerArn =
          Text
pConsumerArn_,
        $sel:trackerName:DisassociateTrackerConsumer' :: Text
trackerName = Text
pTrackerName_
      }

-- | The Amazon Resource Name (ARN) for the geofence collection to be
-- disassociated from the tracker resource. Used when you need to specify a
-- resource across all AWS.
--
-- -   Format example:
--     @arn:aws:geo:region:account-id:geofence-collection\/ExampleGeofenceCollectionConsumer@
disassociateTrackerConsumer_consumerArn :: Lens.Lens' DisassociateTrackerConsumer Prelude.Text
disassociateTrackerConsumer_consumerArn :: Lens' DisassociateTrackerConsumer Text
disassociateTrackerConsumer_consumerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateTrackerConsumer' {Text
consumerArn :: Text
$sel:consumerArn:DisassociateTrackerConsumer' :: DisassociateTrackerConsumer -> Text
consumerArn} -> Text
consumerArn) (\s :: DisassociateTrackerConsumer
s@DisassociateTrackerConsumer' {} Text
a -> DisassociateTrackerConsumer
s {$sel:consumerArn:DisassociateTrackerConsumer' :: Text
consumerArn = Text
a} :: DisassociateTrackerConsumer)

-- | The name of the tracker resource to be dissociated from the consumer.
disassociateTrackerConsumer_trackerName :: Lens.Lens' DisassociateTrackerConsumer Prelude.Text
disassociateTrackerConsumer_trackerName :: Lens' DisassociateTrackerConsumer Text
disassociateTrackerConsumer_trackerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateTrackerConsumer' {Text
trackerName :: Text
$sel:trackerName:DisassociateTrackerConsumer' :: DisassociateTrackerConsumer -> Text
trackerName} -> Text
trackerName) (\s :: DisassociateTrackerConsumer
s@DisassociateTrackerConsumer' {} Text
a -> DisassociateTrackerConsumer
s {$sel:trackerName:DisassociateTrackerConsumer' :: Text
trackerName = Text
a} :: DisassociateTrackerConsumer)

instance Core.AWSRequest DisassociateTrackerConsumer where
  type
    AWSResponse DisassociateTrackerConsumer =
      DisassociateTrackerConsumerResponse
  request :: (Service -> Service)
-> DisassociateTrackerConsumer
-> Request DisassociateTrackerConsumer
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DisassociateTrackerConsumer
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateTrackerConsumer)))
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 -> DisassociateTrackerConsumerResponse
DisassociateTrackerConsumerResponse'
            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 DisassociateTrackerConsumer where
  hashWithSalt :: Int -> DisassociateTrackerConsumer -> Int
hashWithSalt Int
_salt DisassociateTrackerConsumer' {Text
trackerName :: Text
consumerArn :: Text
$sel:trackerName:DisassociateTrackerConsumer' :: DisassociateTrackerConsumer -> Text
$sel:consumerArn:DisassociateTrackerConsumer' :: DisassociateTrackerConsumer -> 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 DisassociateTrackerConsumer where
  rnf :: DisassociateTrackerConsumer -> ()
rnf DisassociateTrackerConsumer' {Text
trackerName :: Text
consumerArn :: Text
$sel:trackerName:DisassociateTrackerConsumer' :: DisassociateTrackerConsumer -> Text
$sel:consumerArn:DisassociateTrackerConsumer' :: DisassociateTrackerConsumer -> 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 DisassociateTrackerConsumer where
  toHeaders :: DisassociateTrackerConsumer -> 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 DisassociateTrackerConsumer where
  toPath :: DisassociateTrackerConsumer -> ByteString
toPath DisassociateTrackerConsumer' {Text
trackerName :: Text
consumerArn :: Text
$sel:trackerName:DisassociateTrackerConsumer' :: DisassociateTrackerConsumer -> Text
$sel:consumerArn:DisassociateTrackerConsumer' :: DisassociateTrackerConsumer -> 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/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
consumerArn
      ]

instance Data.ToQuery DisassociateTrackerConsumer where
  toQuery :: DisassociateTrackerConsumer -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDisassociateTrackerConsumerResponse' smart constructor.
data DisassociateTrackerConsumerResponse = DisassociateTrackerConsumerResponse'
  { -- | The response's http status code.
    DisassociateTrackerConsumerResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisassociateTrackerConsumerResponse
-> DisassociateTrackerConsumerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateTrackerConsumerResponse
-> DisassociateTrackerConsumerResponse -> Bool
$c/= :: DisassociateTrackerConsumerResponse
-> DisassociateTrackerConsumerResponse -> Bool
== :: DisassociateTrackerConsumerResponse
-> DisassociateTrackerConsumerResponse -> Bool
$c== :: DisassociateTrackerConsumerResponse
-> DisassociateTrackerConsumerResponse -> Bool
Prelude.Eq, ReadPrec [DisassociateTrackerConsumerResponse]
ReadPrec DisassociateTrackerConsumerResponse
Int -> ReadS DisassociateTrackerConsumerResponse
ReadS [DisassociateTrackerConsumerResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateTrackerConsumerResponse]
$creadListPrec :: ReadPrec [DisassociateTrackerConsumerResponse]
readPrec :: ReadPrec DisassociateTrackerConsumerResponse
$creadPrec :: ReadPrec DisassociateTrackerConsumerResponse
readList :: ReadS [DisassociateTrackerConsumerResponse]
$creadList :: ReadS [DisassociateTrackerConsumerResponse]
readsPrec :: Int -> ReadS DisassociateTrackerConsumerResponse
$creadsPrec :: Int -> ReadS DisassociateTrackerConsumerResponse
Prelude.Read, Int -> DisassociateTrackerConsumerResponse -> ShowS
[DisassociateTrackerConsumerResponse] -> ShowS
DisassociateTrackerConsumerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateTrackerConsumerResponse] -> ShowS
$cshowList :: [DisassociateTrackerConsumerResponse] -> ShowS
show :: DisassociateTrackerConsumerResponse -> String
$cshow :: DisassociateTrackerConsumerResponse -> String
showsPrec :: Int -> DisassociateTrackerConsumerResponse -> ShowS
$cshowsPrec :: Int -> DisassociateTrackerConsumerResponse -> ShowS
Prelude.Show, forall x.
Rep DisassociateTrackerConsumerResponse x
-> DisassociateTrackerConsumerResponse
forall x.
DisassociateTrackerConsumerResponse
-> Rep DisassociateTrackerConsumerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateTrackerConsumerResponse x
-> DisassociateTrackerConsumerResponse
$cfrom :: forall x.
DisassociateTrackerConsumerResponse
-> Rep DisassociateTrackerConsumerResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateTrackerConsumerResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'httpStatus', 'disassociateTrackerConsumerResponse_httpStatus' - The response's http status code.
newDisassociateTrackerConsumerResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisassociateTrackerConsumerResponse
newDisassociateTrackerConsumerResponse :: Int -> DisassociateTrackerConsumerResponse
newDisassociateTrackerConsumerResponse Int
pHttpStatus_ =
  DisassociateTrackerConsumerResponse'
    { $sel:httpStatus:DisassociateTrackerConsumerResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

-- | The response's http status code.
disassociateTrackerConsumerResponse_httpStatus :: Lens.Lens' DisassociateTrackerConsumerResponse Prelude.Int
disassociateTrackerConsumerResponse_httpStatus :: Lens' DisassociateTrackerConsumerResponse Int
disassociateTrackerConsumerResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateTrackerConsumerResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateTrackerConsumerResponse' :: DisassociateTrackerConsumerResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DisassociateTrackerConsumerResponse
s@DisassociateTrackerConsumerResponse' {} Int
a -> DisassociateTrackerConsumerResponse
s {$sel:httpStatus:DisassociateTrackerConsumerResponse' :: Int
httpStatus = Int
a} :: DisassociateTrackerConsumerResponse)

instance
  Prelude.NFData
    DisassociateTrackerConsumerResponse
  where
  rnf :: DisassociateTrackerConsumerResponse -> ()
rnf DisassociateTrackerConsumerResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateTrackerConsumerResponse' :: DisassociateTrackerConsumerResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus