{-# 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.ElasticSearch.DissociatePackage
(
DissociatePackage (..),
newDissociatePackage,
dissociatePackage_packageID,
dissociatePackage_domainName,
DissociatePackageResponse (..),
newDissociatePackageResponse,
dissociatePackageResponse_domainPackageDetails,
dissociatePackageResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElasticSearch.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data DissociatePackage = DissociatePackage'
{
DissociatePackage -> Text
packageID :: Prelude.Text,
DissociatePackage -> Text
domainName :: Prelude.Text
}
deriving (DissociatePackage -> DissociatePackage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DissociatePackage -> DissociatePackage -> Bool
$c/= :: DissociatePackage -> DissociatePackage -> Bool
== :: DissociatePackage -> DissociatePackage -> Bool
$c== :: DissociatePackage -> DissociatePackage -> Bool
Prelude.Eq, ReadPrec [DissociatePackage]
ReadPrec DissociatePackage
Int -> ReadS DissociatePackage
ReadS [DissociatePackage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DissociatePackage]
$creadListPrec :: ReadPrec [DissociatePackage]
readPrec :: ReadPrec DissociatePackage
$creadPrec :: ReadPrec DissociatePackage
readList :: ReadS [DissociatePackage]
$creadList :: ReadS [DissociatePackage]
readsPrec :: Int -> ReadS DissociatePackage
$creadsPrec :: Int -> ReadS DissociatePackage
Prelude.Read, Int -> DissociatePackage -> ShowS
[DissociatePackage] -> ShowS
DissociatePackage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DissociatePackage] -> ShowS
$cshowList :: [DissociatePackage] -> ShowS
show :: DissociatePackage -> String
$cshow :: DissociatePackage -> String
showsPrec :: Int -> DissociatePackage -> ShowS
$cshowsPrec :: Int -> DissociatePackage -> ShowS
Prelude.Show, forall x. Rep DissociatePackage x -> DissociatePackage
forall x. DissociatePackage -> Rep DissociatePackage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DissociatePackage x -> DissociatePackage
$cfrom :: forall x. DissociatePackage -> Rep DissociatePackage x
Prelude.Generic)
newDissociatePackage ::
Prelude.Text ->
Prelude.Text ->
DissociatePackage
newDissociatePackage :: Text -> Text -> DissociatePackage
newDissociatePackage Text
pPackageID_ Text
pDomainName_ =
DissociatePackage'
{ $sel:packageID:DissociatePackage' :: Text
packageID = Text
pPackageID_,
$sel:domainName:DissociatePackage' :: Text
domainName = Text
pDomainName_
}
dissociatePackage_packageID :: Lens.Lens' DissociatePackage Prelude.Text
dissociatePackage_packageID :: Lens' DissociatePackage Text
dissociatePackage_packageID = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DissociatePackage' {Text
packageID :: Text
$sel:packageID:DissociatePackage' :: DissociatePackage -> Text
packageID} -> Text
packageID) (\s :: DissociatePackage
s@DissociatePackage' {} Text
a -> DissociatePackage
s {$sel:packageID:DissociatePackage' :: Text
packageID = Text
a} :: DissociatePackage)
dissociatePackage_domainName :: Lens.Lens' DissociatePackage Prelude.Text
dissociatePackage_domainName :: Lens' DissociatePackage Text
dissociatePackage_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DissociatePackage' {Text
domainName :: Text
$sel:domainName:DissociatePackage' :: DissociatePackage -> Text
domainName} -> Text
domainName) (\s :: DissociatePackage
s@DissociatePackage' {} Text
a -> DissociatePackage
s {$sel:domainName:DissociatePackage' :: Text
domainName = Text
a} :: DissociatePackage)
instance Core.AWSRequest DissociatePackage where
type
AWSResponse DissociatePackage =
DissociatePackageResponse
request :: (Service -> Service)
-> DissociatePackage -> Request DissociatePackage
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 DissociatePackage
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DissociatePackage)))
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 DomainPackageDetails -> Int -> DissociatePackageResponse
DissociatePackageResponse'
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
"DomainPackageDetails")
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 DissociatePackage where
hashWithSalt :: Int -> DissociatePackage -> Int
hashWithSalt Int
_salt DissociatePackage' {Text
domainName :: Text
packageID :: Text
$sel:domainName:DissociatePackage' :: DissociatePackage -> Text
$sel:packageID:DissociatePackage' :: DissociatePackage -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
packageID
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName
instance Prelude.NFData DissociatePackage where
rnf :: DissociatePackage -> ()
rnf DissociatePackage' {Text
domainName :: Text
packageID :: Text
$sel:domainName:DissociatePackage' :: DissociatePackage -> Text
$sel:packageID:DissociatePackage' :: DissociatePackage -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
packageID
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainName
instance Data.ToHeaders DissociatePackage where
toHeaders :: DissociatePackage -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToJSON DissociatePackage where
toJSON :: DissociatePackage -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)
instance Data.ToPath DissociatePackage where
toPath :: DissociatePackage -> ByteString
toPath DissociatePackage' {Text
domainName :: Text
packageID :: Text
$sel:domainName:DissociatePackage' :: DissociatePackage -> Text
$sel:packageID:DissociatePackage' :: DissociatePackage -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/2015-01-01/packages/dissociate/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
packageID,
ByteString
"/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
domainName
]
instance Data.ToQuery DissociatePackage where
toQuery :: DissociatePackage -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DissociatePackageResponse = DissociatePackageResponse'
{
DissociatePackageResponse -> Maybe DomainPackageDetails
domainPackageDetails :: Prelude.Maybe DomainPackageDetails,
DissociatePackageResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DissociatePackageResponse -> DissociatePackageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DissociatePackageResponse -> DissociatePackageResponse -> Bool
$c/= :: DissociatePackageResponse -> DissociatePackageResponse -> Bool
== :: DissociatePackageResponse -> DissociatePackageResponse -> Bool
$c== :: DissociatePackageResponse -> DissociatePackageResponse -> Bool
Prelude.Eq, ReadPrec [DissociatePackageResponse]
ReadPrec DissociatePackageResponse
Int -> ReadS DissociatePackageResponse
ReadS [DissociatePackageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DissociatePackageResponse]
$creadListPrec :: ReadPrec [DissociatePackageResponse]
readPrec :: ReadPrec DissociatePackageResponse
$creadPrec :: ReadPrec DissociatePackageResponse
readList :: ReadS [DissociatePackageResponse]
$creadList :: ReadS [DissociatePackageResponse]
readsPrec :: Int -> ReadS DissociatePackageResponse
$creadsPrec :: Int -> ReadS DissociatePackageResponse
Prelude.Read, Int -> DissociatePackageResponse -> ShowS
[DissociatePackageResponse] -> ShowS
DissociatePackageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DissociatePackageResponse] -> ShowS
$cshowList :: [DissociatePackageResponse] -> ShowS
show :: DissociatePackageResponse -> String
$cshow :: DissociatePackageResponse -> String
showsPrec :: Int -> DissociatePackageResponse -> ShowS
$cshowsPrec :: Int -> DissociatePackageResponse -> ShowS
Prelude.Show, forall x.
Rep DissociatePackageResponse x -> DissociatePackageResponse
forall x.
DissociatePackageResponse -> Rep DissociatePackageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DissociatePackageResponse x -> DissociatePackageResponse
$cfrom :: forall x.
DissociatePackageResponse -> Rep DissociatePackageResponse x
Prelude.Generic)
newDissociatePackageResponse ::
Prelude.Int ->
DissociatePackageResponse
newDissociatePackageResponse :: Int -> DissociatePackageResponse
newDissociatePackageResponse Int
pHttpStatus_ =
DissociatePackageResponse'
{ $sel:domainPackageDetails:DissociatePackageResponse' :: Maybe DomainPackageDetails
domainPackageDetails =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:DissociatePackageResponse' :: Int
httpStatus = Int
pHttpStatus_
}
dissociatePackageResponse_domainPackageDetails :: Lens.Lens' DissociatePackageResponse (Prelude.Maybe DomainPackageDetails)
dissociatePackageResponse_domainPackageDetails :: Lens' DissociatePackageResponse (Maybe DomainPackageDetails)
dissociatePackageResponse_domainPackageDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DissociatePackageResponse' {Maybe DomainPackageDetails
domainPackageDetails :: Maybe DomainPackageDetails
$sel:domainPackageDetails:DissociatePackageResponse' :: DissociatePackageResponse -> Maybe DomainPackageDetails
domainPackageDetails} -> Maybe DomainPackageDetails
domainPackageDetails) (\s :: DissociatePackageResponse
s@DissociatePackageResponse' {} Maybe DomainPackageDetails
a -> DissociatePackageResponse
s {$sel:domainPackageDetails:DissociatePackageResponse' :: Maybe DomainPackageDetails
domainPackageDetails = Maybe DomainPackageDetails
a} :: DissociatePackageResponse)
dissociatePackageResponse_httpStatus :: Lens.Lens' DissociatePackageResponse Prelude.Int
dissociatePackageResponse_httpStatus :: Lens' DissociatePackageResponse Int
dissociatePackageResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DissociatePackageResponse' {Int
httpStatus :: Int
$sel:httpStatus:DissociatePackageResponse' :: DissociatePackageResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DissociatePackageResponse
s@DissociatePackageResponse' {} Int
a -> DissociatePackageResponse
s {$sel:httpStatus:DissociatePackageResponse' :: Int
httpStatus = Int
a} :: DissociatePackageResponse)
instance Prelude.NFData DissociatePackageResponse where
rnf :: DissociatePackageResponse -> ()
rnf DissociatePackageResponse' {Int
Maybe DomainPackageDetails
httpStatus :: Int
domainPackageDetails :: Maybe DomainPackageDetails
$sel:httpStatus:DissociatePackageResponse' :: DissociatePackageResponse -> Int
$sel:domainPackageDetails:DissociatePackageResponse' :: DissociatePackageResponse -> Maybe DomainPackageDetails
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe DomainPackageDetails
domainPackageDetails
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus