{-# 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.WorkMail.CreateGroup
(
CreateGroup (..),
newCreateGroup,
createGroup_organizationId,
createGroup_name,
CreateGroupResponse (..),
newCreateGroupResponse,
createGroupResponse_groupId,
createGroupResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.WorkMail.Types
data CreateGroup = CreateGroup'
{
CreateGroup -> Text
organizationId :: Prelude.Text,
CreateGroup -> Text
name :: Prelude.Text
}
deriving (CreateGroup -> CreateGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateGroup -> CreateGroup -> Bool
$c/= :: CreateGroup -> CreateGroup -> Bool
== :: CreateGroup -> CreateGroup -> Bool
$c== :: CreateGroup -> CreateGroup -> Bool
Prelude.Eq, ReadPrec [CreateGroup]
ReadPrec CreateGroup
Int -> ReadS CreateGroup
ReadS [CreateGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateGroup]
$creadListPrec :: ReadPrec [CreateGroup]
readPrec :: ReadPrec CreateGroup
$creadPrec :: ReadPrec CreateGroup
readList :: ReadS [CreateGroup]
$creadList :: ReadS [CreateGroup]
readsPrec :: Int -> ReadS CreateGroup
$creadsPrec :: Int -> ReadS CreateGroup
Prelude.Read, Int -> CreateGroup -> ShowS
[CreateGroup] -> ShowS
CreateGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateGroup] -> ShowS
$cshowList :: [CreateGroup] -> ShowS
show :: CreateGroup -> String
$cshow :: CreateGroup -> String
showsPrec :: Int -> CreateGroup -> ShowS
$cshowsPrec :: Int -> CreateGroup -> ShowS
Prelude.Show, forall x. Rep CreateGroup x -> CreateGroup
forall x. CreateGroup -> Rep CreateGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateGroup x -> CreateGroup
$cfrom :: forall x. CreateGroup -> Rep CreateGroup x
Prelude.Generic)
newCreateGroup ::
Prelude.Text ->
Prelude.Text ->
CreateGroup
newCreateGroup :: Text -> Text -> CreateGroup
newCreateGroup Text
pOrganizationId_ Text
pName_ =
CreateGroup'
{ $sel:organizationId:CreateGroup' :: Text
organizationId = Text
pOrganizationId_,
$sel:name:CreateGroup' :: Text
name = Text
pName_
}
createGroup_organizationId :: Lens.Lens' CreateGroup Prelude.Text
createGroup_organizationId :: Lens' CreateGroup Text
createGroup_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Text
organizationId :: Text
$sel:organizationId:CreateGroup' :: CreateGroup -> Text
organizationId} -> Text
organizationId) (\s :: CreateGroup
s@CreateGroup' {} Text
a -> CreateGroup
s {$sel:organizationId:CreateGroup' :: Text
organizationId = Text
a} :: CreateGroup)
createGroup_name :: Lens.Lens' CreateGroup Prelude.Text
createGroup_name :: Lens' CreateGroup Text
createGroup_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Text
name :: Text
$sel:name:CreateGroup' :: CreateGroup -> Text
name} -> Text
name) (\s :: CreateGroup
s@CreateGroup' {} Text
a -> CreateGroup
s {$sel:name:CreateGroup' :: Text
name = Text
a} :: CreateGroup)
instance Core.AWSRequest CreateGroup where
type AWSResponse CreateGroup = CreateGroupResponse
request :: (Service -> Service) -> CreateGroup -> Request CreateGroup
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 CreateGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateGroup)))
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 -> CreateGroupResponse
CreateGroupResponse'
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
"GroupId")
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 CreateGroup where
hashWithSalt :: Int -> CreateGroup -> Int
hashWithSalt Int
_salt CreateGroup' {Text
name :: Text
organizationId :: Text
$sel:name:CreateGroup' :: CreateGroup -> Text
$sel:organizationId:CreateGroup' :: CreateGroup -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
instance Prelude.NFData CreateGroup where
rnf :: CreateGroup -> ()
rnf CreateGroup' {Text
name :: Text
organizationId :: Text
$sel:name:CreateGroup' :: CreateGroup -> Text
$sel:organizationId:CreateGroup' :: CreateGroup -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
instance Data.ToHeaders CreateGroup where
toHeaders :: CreateGroup -> 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
"WorkMailService.CreateGroup" ::
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 CreateGroup where
toJSON :: CreateGroup -> Value
toJSON CreateGroup' {Text
name :: Text
organizationId :: Text
$sel:name:CreateGroup' :: CreateGroup -> Text
$sel:organizationId:CreateGroup' :: CreateGroup -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ forall a. a -> Maybe a
Prelude.Just
(Key
"OrganizationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationId),
forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
]
)
instance Data.ToPath CreateGroup where
toPath :: CreateGroup -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CreateGroup where
toQuery :: CreateGroup -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CreateGroupResponse = CreateGroupResponse'
{
CreateGroupResponse -> Maybe Text
groupId :: Prelude.Maybe Prelude.Text,
CreateGroupResponse -> Int
httpStatus :: Prelude.Int
}
deriving (CreateGroupResponse -> CreateGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateGroupResponse -> CreateGroupResponse -> Bool
$c/= :: CreateGroupResponse -> CreateGroupResponse -> Bool
== :: CreateGroupResponse -> CreateGroupResponse -> Bool
$c== :: CreateGroupResponse -> CreateGroupResponse -> Bool
Prelude.Eq, ReadPrec [CreateGroupResponse]
ReadPrec CreateGroupResponse
Int -> ReadS CreateGroupResponse
ReadS [CreateGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateGroupResponse]
$creadListPrec :: ReadPrec [CreateGroupResponse]
readPrec :: ReadPrec CreateGroupResponse
$creadPrec :: ReadPrec CreateGroupResponse
readList :: ReadS [CreateGroupResponse]
$creadList :: ReadS [CreateGroupResponse]
readsPrec :: Int -> ReadS CreateGroupResponse
$creadsPrec :: Int -> ReadS CreateGroupResponse
Prelude.Read, Int -> CreateGroupResponse -> ShowS
[CreateGroupResponse] -> ShowS
CreateGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateGroupResponse] -> ShowS
$cshowList :: [CreateGroupResponse] -> ShowS
show :: CreateGroupResponse -> String
$cshow :: CreateGroupResponse -> String
showsPrec :: Int -> CreateGroupResponse -> ShowS
$cshowsPrec :: Int -> CreateGroupResponse -> ShowS
Prelude.Show, forall x. Rep CreateGroupResponse x -> CreateGroupResponse
forall x. CreateGroupResponse -> Rep CreateGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateGroupResponse x -> CreateGroupResponse
$cfrom :: forall x. CreateGroupResponse -> Rep CreateGroupResponse x
Prelude.Generic)
newCreateGroupResponse ::
Prelude.Int ->
CreateGroupResponse
newCreateGroupResponse :: Int -> CreateGroupResponse
newCreateGroupResponse Int
pHttpStatus_ =
CreateGroupResponse'
{ $sel:groupId:CreateGroupResponse' :: Maybe Text
groupId = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:CreateGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
}
createGroupResponse_groupId :: Lens.Lens' CreateGroupResponse (Prelude.Maybe Prelude.Text)
createGroupResponse_groupId :: Lens' CreateGroupResponse (Maybe Text)
createGroupResponse_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroupResponse' {Maybe Text
groupId :: Maybe Text
$sel:groupId:CreateGroupResponse' :: CreateGroupResponse -> Maybe Text
groupId} -> Maybe Text
groupId) (\s :: CreateGroupResponse
s@CreateGroupResponse' {} Maybe Text
a -> CreateGroupResponse
s {$sel:groupId:CreateGroupResponse' :: Maybe Text
groupId = Maybe Text
a} :: CreateGroupResponse)
createGroupResponse_httpStatus :: Lens.Lens' CreateGroupResponse Prelude.Int
createGroupResponse_httpStatus :: Lens' CreateGroupResponse Int
createGroupResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroupResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateGroupResponse' :: CreateGroupResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateGroupResponse
s@CreateGroupResponse' {} Int
a -> CreateGroupResponse
s {$sel:httpStatus:CreateGroupResponse' :: Int
httpStatus = Int
a} :: CreateGroupResponse)
instance Prelude.NFData CreateGroupResponse where
rnf :: CreateGroupResponse -> ()
rnf CreateGroupResponse' {Int
Maybe Text
httpStatus :: Int
groupId :: Maybe Text
$sel:httpStatus:CreateGroupResponse' :: CreateGroupResponse -> Int
$sel:groupId:CreateGroupResponse' :: CreateGroupResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus