{-# 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.Organizations.EnableAllFeatures
(
EnableAllFeatures (..),
newEnableAllFeatures,
EnableAllFeaturesResponse (..),
newEnableAllFeaturesResponse,
enableAllFeaturesResponse_handshake,
enableAllFeaturesResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Organizations.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data EnableAllFeatures = EnableAllFeatures'
{
}
deriving (EnableAllFeatures -> EnableAllFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableAllFeatures -> EnableAllFeatures -> Bool
$c/= :: EnableAllFeatures -> EnableAllFeatures -> Bool
== :: EnableAllFeatures -> EnableAllFeatures -> Bool
$c== :: EnableAllFeatures -> EnableAllFeatures -> Bool
Prelude.Eq, ReadPrec [EnableAllFeatures]
ReadPrec EnableAllFeatures
Int -> ReadS EnableAllFeatures
ReadS [EnableAllFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableAllFeatures]
$creadListPrec :: ReadPrec [EnableAllFeatures]
readPrec :: ReadPrec EnableAllFeatures
$creadPrec :: ReadPrec EnableAllFeatures
readList :: ReadS [EnableAllFeatures]
$creadList :: ReadS [EnableAllFeatures]
readsPrec :: Int -> ReadS EnableAllFeatures
$creadsPrec :: Int -> ReadS EnableAllFeatures
Prelude.Read, Int -> EnableAllFeatures -> ShowS
[EnableAllFeatures] -> ShowS
EnableAllFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableAllFeatures] -> ShowS
$cshowList :: [EnableAllFeatures] -> ShowS
show :: EnableAllFeatures -> String
$cshow :: EnableAllFeatures -> String
showsPrec :: Int -> EnableAllFeatures -> ShowS
$cshowsPrec :: Int -> EnableAllFeatures -> ShowS
Prelude.Show, forall x. Rep EnableAllFeatures x -> EnableAllFeatures
forall x. EnableAllFeatures -> Rep EnableAllFeatures x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableAllFeatures x -> EnableAllFeatures
$cfrom :: forall x. EnableAllFeatures -> Rep EnableAllFeatures x
Prelude.Generic)
newEnableAllFeatures ::
EnableAllFeatures
newEnableAllFeatures :: EnableAllFeatures
newEnableAllFeatures = EnableAllFeatures
EnableAllFeatures'
instance Core.AWSRequest EnableAllFeatures where
type
AWSResponse EnableAllFeatures =
EnableAllFeaturesResponse
request :: (Service -> Service)
-> EnableAllFeatures -> Request EnableAllFeatures
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 EnableAllFeatures
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse EnableAllFeatures)))
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 Handshake -> Int -> EnableAllFeaturesResponse
EnableAllFeaturesResponse'
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
"Handshake")
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 EnableAllFeatures where
hashWithSalt :: Int -> EnableAllFeatures -> Int
hashWithSalt Int
_salt EnableAllFeatures
_ =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()
instance Prelude.NFData EnableAllFeatures where
rnf :: EnableAllFeatures -> ()
rnf EnableAllFeatures
_ = ()
instance Data.ToHeaders EnableAllFeatures where
toHeaders :: EnableAllFeatures -> 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
"AWSOrganizationsV20161128.EnableAllFeatures" ::
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 EnableAllFeatures where
toJSON :: EnableAllFeatures -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)
instance Data.ToPath EnableAllFeatures where
toPath :: EnableAllFeatures -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery EnableAllFeatures where
toQuery :: EnableAllFeatures -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data EnableAllFeaturesResponse = EnableAllFeaturesResponse'
{
EnableAllFeaturesResponse -> Maybe Handshake
handshake :: Prelude.Maybe Handshake,
EnableAllFeaturesResponse -> Int
httpStatus :: Prelude.Int
}
deriving (EnableAllFeaturesResponse -> EnableAllFeaturesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableAllFeaturesResponse -> EnableAllFeaturesResponse -> Bool
$c/= :: EnableAllFeaturesResponse -> EnableAllFeaturesResponse -> Bool
== :: EnableAllFeaturesResponse -> EnableAllFeaturesResponse -> Bool
$c== :: EnableAllFeaturesResponse -> EnableAllFeaturesResponse -> Bool
Prelude.Eq, Int -> EnableAllFeaturesResponse -> ShowS
[EnableAllFeaturesResponse] -> ShowS
EnableAllFeaturesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableAllFeaturesResponse] -> ShowS
$cshowList :: [EnableAllFeaturesResponse] -> ShowS
show :: EnableAllFeaturesResponse -> String
$cshow :: EnableAllFeaturesResponse -> String
showsPrec :: Int -> EnableAllFeaturesResponse -> ShowS
$cshowsPrec :: Int -> EnableAllFeaturesResponse -> ShowS
Prelude.Show, forall x.
Rep EnableAllFeaturesResponse x -> EnableAllFeaturesResponse
forall x.
EnableAllFeaturesResponse -> Rep EnableAllFeaturesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EnableAllFeaturesResponse x -> EnableAllFeaturesResponse
$cfrom :: forall x.
EnableAllFeaturesResponse -> Rep EnableAllFeaturesResponse x
Prelude.Generic)
newEnableAllFeaturesResponse ::
Prelude.Int ->
EnableAllFeaturesResponse
newEnableAllFeaturesResponse :: Int -> EnableAllFeaturesResponse
newEnableAllFeaturesResponse Int
pHttpStatus_ =
EnableAllFeaturesResponse'
{ $sel:handshake:EnableAllFeaturesResponse' :: Maybe Handshake
handshake =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:EnableAllFeaturesResponse' :: Int
httpStatus = Int
pHttpStatus_
}
enableAllFeaturesResponse_handshake :: Lens.Lens' EnableAllFeaturesResponse (Prelude.Maybe Handshake)
enableAllFeaturesResponse_handshake :: Lens' EnableAllFeaturesResponse (Maybe Handshake)
enableAllFeaturesResponse_handshake = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableAllFeaturesResponse' {Maybe Handshake
handshake :: Maybe Handshake
$sel:handshake:EnableAllFeaturesResponse' :: EnableAllFeaturesResponse -> Maybe Handshake
handshake} -> Maybe Handshake
handshake) (\s :: EnableAllFeaturesResponse
s@EnableAllFeaturesResponse' {} Maybe Handshake
a -> EnableAllFeaturesResponse
s {$sel:handshake:EnableAllFeaturesResponse' :: Maybe Handshake
handshake = Maybe Handshake
a} :: EnableAllFeaturesResponse)
enableAllFeaturesResponse_httpStatus :: Lens.Lens' EnableAllFeaturesResponse Prelude.Int
enableAllFeaturesResponse_httpStatus :: Lens' EnableAllFeaturesResponse Int
enableAllFeaturesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableAllFeaturesResponse' {Int
httpStatus :: Int
$sel:httpStatus:EnableAllFeaturesResponse' :: EnableAllFeaturesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: EnableAllFeaturesResponse
s@EnableAllFeaturesResponse' {} Int
a -> EnableAllFeaturesResponse
s {$sel:httpStatus:EnableAllFeaturesResponse' :: Int
httpStatus = Int
a} :: EnableAllFeaturesResponse)
instance Prelude.NFData EnableAllFeaturesResponse where
rnf :: EnableAllFeaturesResponse -> ()
rnf EnableAllFeaturesResponse' {Int
Maybe Handshake
httpStatus :: Int
handshake :: Maybe Handshake
$sel:httpStatus:EnableAllFeaturesResponse' :: EnableAllFeaturesResponse -> Int
$sel:handshake:EnableAllFeaturesResponse' :: EnableAllFeaturesResponse -> Maybe Handshake
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Handshake
handshake
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus