{-# 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.DirectoryService.CreateSnapshot
(
CreateSnapshot (..),
newCreateSnapshot,
createSnapshot_name,
createSnapshot_directoryId,
CreateSnapshotResponse (..),
newCreateSnapshotResponse,
createSnapshotResponse_snapshotId,
createSnapshotResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DirectoryService.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data CreateSnapshot = CreateSnapshot'
{
CreateSnapshot -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
CreateSnapshot -> Text
directoryId :: Prelude.Text
}
deriving (CreateSnapshot -> CreateSnapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSnapshot -> CreateSnapshot -> Bool
$c/= :: CreateSnapshot -> CreateSnapshot -> Bool
== :: CreateSnapshot -> CreateSnapshot -> Bool
$c== :: CreateSnapshot -> CreateSnapshot -> Bool
Prelude.Eq, ReadPrec [CreateSnapshot]
ReadPrec CreateSnapshot
Int -> ReadS CreateSnapshot
ReadS [CreateSnapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSnapshot]
$creadListPrec :: ReadPrec [CreateSnapshot]
readPrec :: ReadPrec CreateSnapshot
$creadPrec :: ReadPrec CreateSnapshot
readList :: ReadS [CreateSnapshot]
$creadList :: ReadS [CreateSnapshot]
readsPrec :: Int -> ReadS CreateSnapshot
$creadsPrec :: Int -> ReadS CreateSnapshot
Prelude.Read, Int -> CreateSnapshot -> ShowS
[CreateSnapshot] -> ShowS
CreateSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSnapshot] -> ShowS
$cshowList :: [CreateSnapshot] -> ShowS
show :: CreateSnapshot -> String
$cshow :: CreateSnapshot -> String
showsPrec :: Int -> CreateSnapshot -> ShowS
$cshowsPrec :: Int -> CreateSnapshot -> ShowS
Prelude.Show, forall x. Rep CreateSnapshot x -> CreateSnapshot
forall x. CreateSnapshot -> Rep CreateSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSnapshot x -> CreateSnapshot
$cfrom :: forall x. CreateSnapshot -> Rep CreateSnapshot x
Prelude.Generic)
newCreateSnapshot ::
Prelude.Text ->
CreateSnapshot
newCreateSnapshot :: Text -> CreateSnapshot
newCreateSnapshot Text
pDirectoryId_ =
CreateSnapshot'
{ $sel:name:CreateSnapshot' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:directoryId:CreateSnapshot' :: Text
directoryId = Text
pDirectoryId_
}
createSnapshot_name :: Lens.Lens' CreateSnapshot (Prelude.Maybe Prelude.Text)
createSnapshot_name :: Lens' CreateSnapshot (Maybe Text)
createSnapshot_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Maybe Text
name :: Maybe Text
$sel:name:CreateSnapshot' :: CreateSnapshot -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateSnapshot
s@CreateSnapshot' {} Maybe Text
a -> CreateSnapshot
s {$sel:name:CreateSnapshot' :: Maybe Text
name = Maybe Text
a} :: CreateSnapshot)
createSnapshot_directoryId :: Lens.Lens' CreateSnapshot Prelude.Text
createSnapshot_directoryId :: Lens' CreateSnapshot Text
createSnapshot_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshot' {Text
directoryId :: Text
$sel:directoryId:CreateSnapshot' :: CreateSnapshot -> Text
directoryId} -> Text
directoryId) (\s :: CreateSnapshot
s@CreateSnapshot' {} Text
a -> CreateSnapshot
s {$sel:directoryId:CreateSnapshot' :: Text
directoryId = Text
a} :: CreateSnapshot)
instance Core.AWSRequest CreateSnapshot where
type
AWSResponse CreateSnapshot =
CreateSnapshotResponse
request :: (Service -> Service) -> CreateSnapshot -> Request CreateSnapshot
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 CreateSnapshot
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateSnapshot)))
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 -> Int -> CreateSnapshotResponse
CreateSnapshotResponse'
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
"SnapshotId")
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 CreateSnapshot where
hashWithSalt :: Int -> CreateSnapshot -> Int
hashWithSalt Int
_salt CreateSnapshot' {Maybe Text
Text
directoryId :: Text
name :: Maybe Text
$sel:directoryId:CreateSnapshot' :: CreateSnapshot -> Text
$sel:name:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryId
instance Prelude.NFData CreateSnapshot where
rnf :: CreateSnapshot -> ()
rnf CreateSnapshot' {Maybe Text
Text
directoryId :: Text
name :: Maybe Text
$sel:directoryId:CreateSnapshot' :: CreateSnapshot -> Text
$sel:name:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
directoryId
instance Data.ToHeaders CreateSnapshot where
toHeaders :: CreateSnapshot -> 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
"DirectoryService_20150416.CreateSnapshot" ::
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 CreateSnapshot where
toJSON :: CreateSnapshot -> Value
toJSON CreateSnapshot' {Maybe Text
Text
directoryId :: Text
name :: Maybe Text
$sel:directoryId:CreateSnapshot' :: CreateSnapshot -> Text
$sel:name:CreateSnapshot' :: CreateSnapshot -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"Name" 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
name,
forall a. a -> Maybe a
Prelude.Just (Key
"DirectoryId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
directoryId)
]
)
instance Data.ToPath CreateSnapshot where
toPath :: CreateSnapshot -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CreateSnapshot where
toQuery :: CreateSnapshot -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CreateSnapshotResponse = CreateSnapshotResponse'
{
CreateSnapshotResponse -> Maybe Text
snapshotId :: Prelude.Maybe Prelude.Text,
CreateSnapshotResponse -> Int
httpStatus :: Prelude.Int
}
deriving (CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
$c/= :: CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
== :: CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
$c== :: CreateSnapshotResponse -> CreateSnapshotResponse -> Bool
Prelude.Eq, ReadPrec [CreateSnapshotResponse]
ReadPrec CreateSnapshotResponse
Int -> ReadS CreateSnapshotResponse
ReadS [CreateSnapshotResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSnapshotResponse]
$creadListPrec :: ReadPrec [CreateSnapshotResponse]
readPrec :: ReadPrec CreateSnapshotResponse
$creadPrec :: ReadPrec CreateSnapshotResponse
readList :: ReadS [CreateSnapshotResponse]
$creadList :: ReadS [CreateSnapshotResponse]
readsPrec :: Int -> ReadS CreateSnapshotResponse
$creadsPrec :: Int -> ReadS CreateSnapshotResponse
Prelude.Read, Int -> CreateSnapshotResponse -> ShowS
[CreateSnapshotResponse] -> ShowS
CreateSnapshotResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSnapshotResponse] -> ShowS
$cshowList :: [CreateSnapshotResponse] -> ShowS
show :: CreateSnapshotResponse -> String
$cshow :: CreateSnapshotResponse -> String
showsPrec :: Int -> CreateSnapshotResponse -> ShowS
$cshowsPrec :: Int -> CreateSnapshotResponse -> ShowS
Prelude.Show, forall x. Rep CreateSnapshotResponse x -> CreateSnapshotResponse
forall x. CreateSnapshotResponse -> Rep CreateSnapshotResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSnapshotResponse x -> CreateSnapshotResponse
$cfrom :: forall x. CreateSnapshotResponse -> Rep CreateSnapshotResponse x
Prelude.Generic)
newCreateSnapshotResponse ::
Prelude.Int ->
CreateSnapshotResponse
newCreateSnapshotResponse :: Int -> CreateSnapshotResponse
newCreateSnapshotResponse Int
pHttpStatus_ =
CreateSnapshotResponse'
{ $sel:snapshotId:CreateSnapshotResponse' :: Maybe Text
snapshotId =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:CreateSnapshotResponse' :: Int
httpStatus = Int
pHttpStatus_
}
createSnapshotResponse_snapshotId :: Lens.Lens' CreateSnapshotResponse (Prelude.Maybe Prelude.Text)
createSnapshotResponse_snapshotId :: Lens' CreateSnapshotResponse (Maybe Text)
createSnapshotResponse_snapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshotResponse' {Maybe Text
snapshotId :: Maybe Text
$sel:snapshotId:CreateSnapshotResponse' :: CreateSnapshotResponse -> Maybe Text
snapshotId} -> Maybe Text
snapshotId) (\s :: CreateSnapshotResponse
s@CreateSnapshotResponse' {} Maybe Text
a -> CreateSnapshotResponse
s {$sel:snapshotId:CreateSnapshotResponse' :: Maybe Text
snapshotId = Maybe Text
a} :: CreateSnapshotResponse)
createSnapshotResponse_httpStatus :: Lens.Lens' CreateSnapshotResponse Prelude.Int
createSnapshotResponse_httpStatus :: Lens' CreateSnapshotResponse Int
createSnapshotResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshotResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateSnapshotResponse' :: CreateSnapshotResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateSnapshotResponse
s@CreateSnapshotResponse' {} Int
a -> CreateSnapshotResponse
s {$sel:httpStatus:CreateSnapshotResponse' :: Int
httpStatus = Int
a} :: CreateSnapshotResponse)
instance Prelude.NFData CreateSnapshotResponse where
rnf :: CreateSnapshotResponse -> ()
rnf CreateSnapshotResponse' {Int
Maybe Text
httpStatus :: Int
snapshotId :: Maybe Text
$sel:httpStatus:CreateSnapshotResponse' :: CreateSnapshotResponse -> Int
$sel:snapshotId:CreateSnapshotResponse' :: CreateSnapshotResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snapshotId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus