{-# 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.AppSync.CreateType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a @Type@ object.
module Amazonka.AppSync.CreateType
  ( -- * Creating a Request
    CreateType (..),
    newCreateType,

    -- * Request Lenses
    createType_apiId,
    createType_definition,
    createType_format,

    -- * Destructuring the Response
    CreateTypeResponse (..),
    newCreateTypeResponse,

    -- * Response Lenses
    createTypeResponse_type,
    createTypeResponse_httpStatus,
  )
where

import Amazonka.AppSync.Types
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

-- | /See:/ 'newCreateType' smart constructor.
data CreateType = CreateType'
  { -- | The API ID.
    CreateType -> Text
apiId :: Prelude.Text,
    -- | The type definition, in GraphQL Schema Definition Language (SDL) format.
    --
    -- For more information, see the
    -- <http://graphql.org/learn/schema/ GraphQL SDL documentation>.
    CreateType -> Text
definition :: Prelude.Text,
    -- | The type format: SDL or JSON.
    CreateType -> TypeDefinitionFormat
format :: TypeDefinitionFormat
  }
  deriving (CreateType -> CreateType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateType -> CreateType -> Bool
$c/= :: CreateType -> CreateType -> Bool
== :: CreateType -> CreateType -> Bool
$c== :: CreateType -> CreateType -> Bool
Prelude.Eq, ReadPrec [CreateType]
ReadPrec CreateType
Int -> ReadS CreateType
ReadS [CreateType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateType]
$creadListPrec :: ReadPrec [CreateType]
readPrec :: ReadPrec CreateType
$creadPrec :: ReadPrec CreateType
readList :: ReadS [CreateType]
$creadList :: ReadS [CreateType]
readsPrec :: Int -> ReadS CreateType
$creadsPrec :: Int -> ReadS CreateType
Prelude.Read, Int -> CreateType -> ShowS
[CreateType] -> ShowS
CreateType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateType] -> ShowS
$cshowList :: [CreateType] -> ShowS
show :: CreateType -> String
$cshow :: CreateType -> String
showsPrec :: Int -> CreateType -> ShowS
$cshowsPrec :: Int -> CreateType -> ShowS
Prelude.Show, forall x. Rep CreateType x -> CreateType
forall x. CreateType -> Rep CreateType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateType x -> CreateType
$cfrom :: forall x. CreateType -> Rep CreateType x
Prelude.Generic)

-- |
-- Create a value of 'CreateType' 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:
--
-- 'apiId', 'createType_apiId' - The API ID.
--
-- 'definition', 'createType_definition' - The type definition, in GraphQL Schema Definition Language (SDL) format.
--
-- For more information, see the
-- <http://graphql.org/learn/schema/ GraphQL SDL documentation>.
--
-- 'format', 'createType_format' - The type format: SDL or JSON.
newCreateType ::
  -- | 'apiId'
  Prelude.Text ->
  -- | 'definition'
  Prelude.Text ->
  -- | 'format'
  TypeDefinitionFormat ->
  CreateType
newCreateType :: Text -> Text -> TypeDefinitionFormat -> CreateType
newCreateType Text
pApiId_ Text
pDefinition_ TypeDefinitionFormat
pFormat_ =
  CreateType'
    { $sel:apiId:CreateType' :: Text
apiId = Text
pApiId_,
      $sel:definition:CreateType' :: Text
definition = Text
pDefinition_,
      $sel:format:CreateType' :: TypeDefinitionFormat
format = TypeDefinitionFormat
pFormat_
    }

-- | The API ID.
createType_apiId :: Lens.Lens' CreateType Prelude.Text
createType_apiId :: Lens' CreateType Text
createType_apiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateType' {Text
apiId :: Text
$sel:apiId:CreateType' :: CreateType -> Text
apiId} -> Text
apiId) (\s :: CreateType
s@CreateType' {} Text
a -> CreateType
s {$sel:apiId:CreateType' :: Text
apiId = Text
a} :: CreateType)

-- | The type definition, in GraphQL Schema Definition Language (SDL) format.
--
-- For more information, see the
-- <http://graphql.org/learn/schema/ GraphQL SDL documentation>.
createType_definition :: Lens.Lens' CreateType Prelude.Text
createType_definition :: Lens' CreateType Text
createType_definition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateType' {Text
definition :: Text
$sel:definition:CreateType' :: CreateType -> Text
definition} -> Text
definition) (\s :: CreateType
s@CreateType' {} Text
a -> CreateType
s {$sel:definition:CreateType' :: Text
definition = Text
a} :: CreateType)

-- | The type format: SDL or JSON.
createType_format :: Lens.Lens' CreateType TypeDefinitionFormat
createType_format :: Lens' CreateType TypeDefinitionFormat
createType_format = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateType' {TypeDefinitionFormat
format :: TypeDefinitionFormat
$sel:format:CreateType' :: CreateType -> TypeDefinitionFormat
format} -> TypeDefinitionFormat
format) (\s :: CreateType
s@CreateType' {} TypeDefinitionFormat
a -> CreateType
s {$sel:format:CreateType' :: TypeDefinitionFormat
format = TypeDefinitionFormat
a} :: CreateType)

instance Core.AWSRequest CreateType where
  type AWSResponse CreateType = CreateTypeResponse
  request :: (Service -> Service) -> CreateType -> Request CreateType
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 CreateType
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateType)))
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 Type -> Int -> CreateTypeResponse
CreateTypeResponse'
            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
"type")
            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 CreateType where
  hashWithSalt :: Int -> CreateType -> Int
hashWithSalt Int
_salt CreateType' {Text
TypeDefinitionFormat
format :: TypeDefinitionFormat
definition :: Text
apiId :: Text
$sel:format:CreateType' :: CreateType -> TypeDefinitionFormat
$sel:definition:CreateType' :: CreateType -> Text
$sel:apiId:CreateType' :: CreateType -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
apiId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
definition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TypeDefinitionFormat
format

instance Prelude.NFData CreateType where
  rnf :: CreateType -> ()
rnf CreateType' {Text
TypeDefinitionFormat
format :: TypeDefinitionFormat
definition :: Text
apiId :: Text
$sel:format:CreateType' :: CreateType -> TypeDefinitionFormat
$sel:definition:CreateType' :: CreateType -> Text
$sel:apiId:CreateType' :: CreateType -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
apiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
definition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TypeDefinitionFormat
format

instance Data.ToHeaders CreateType where
  toHeaders :: CreateType -> 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.ToJSON CreateType where
  toJSON :: CreateType -> Value
toJSON CreateType' {Text
TypeDefinitionFormat
format :: TypeDefinitionFormat
definition :: Text
apiId :: Text
$sel:format:CreateType' :: CreateType -> TypeDefinitionFormat
$sel:definition:CreateType' :: CreateType -> Text
$sel:apiId:CreateType' :: CreateType -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"definition" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
definition),
            forall a. a -> Maybe a
Prelude.Just (Key
"format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TypeDefinitionFormat
format)
          ]
      )

instance Data.ToPath CreateType where
  toPath :: CreateType -> ByteString
toPath CreateType' {Text
TypeDefinitionFormat
format :: TypeDefinitionFormat
definition :: Text
apiId :: Text
$sel:format:CreateType' :: CreateType -> TypeDefinitionFormat
$sel:definition:CreateType' :: CreateType -> Text
$sel:apiId:CreateType' :: CreateType -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/apis/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
apiId, ByteString
"/types"]

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

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

-- |
-- Create a value of 'CreateTypeResponse' 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:
--
-- 'type'', 'createTypeResponse_type' - The @Type@ object.
--
-- 'httpStatus', 'createTypeResponse_httpStatus' - The response's http status code.
newCreateTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateTypeResponse
newCreateTypeResponse :: Int -> CreateTypeResponse
newCreateTypeResponse Int
pHttpStatus_ =
  CreateTypeResponse'
    { $sel:type':CreateTypeResponse' :: Maybe Type
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @Type@ object.
createTypeResponse_type :: Lens.Lens' CreateTypeResponse (Prelude.Maybe Type)
createTypeResponse_type :: Lens' CreateTypeResponse (Maybe Type)
createTypeResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTypeResponse' {Maybe Type
type' :: Maybe Type
$sel:type':CreateTypeResponse' :: CreateTypeResponse -> Maybe Type
type'} -> Maybe Type
type') (\s :: CreateTypeResponse
s@CreateTypeResponse' {} Maybe Type
a -> CreateTypeResponse
s {$sel:type':CreateTypeResponse' :: Maybe Type
type' = Maybe Type
a} :: CreateTypeResponse)

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

instance Prelude.NFData CreateTypeResponse where
  rnf :: CreateTypeResponse -> ()
rnf CreateTypeResponse' {Int
Maybe Type
httpStatus :: Int
type' :: Maybe Type
$sel:httpStatus:CreateTypeResponse' :: CreateTypeResponse -> Int
$sel:type':CreateTypeResponse' :: CreateTypeResponse -> Maybe Type
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Type
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus