{-# 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.Schemas.CreateSchema
-- 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 schema definition.
--
-- Inactive schemas will be deleted after two years.
module Amazonka.Schemas.CreateSchema
  ( -- * Creating a Request
    CreateSchema (..),
    newCreateSchema,

    -- * Request Lenses
    createSchema_description,
    createSchema_tags,
    createSchema_registryName,
    createSchema_schemaName,
    createSchema_type,
    createSchema_content,

    -- * Destructuring the Response
    CreateSchemaResponse (..),
    newCreateSchemaResponse,

    -- * Response Lenses
    createSchemaResponse_description,
    createSchemaResponse_lastModified,
    createSchemaResponse_schemaArn,
    createSchemaResponse_schemaName,
    createSchemaResponse_schemaVersion,
    createSchemaResponse_tags,
    createSchemaResponse_type,
    createSchemaResponse_versionCreatedDate,
    createSchemaResponse_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.Schemas.Types

-- | /See:/ 'newCreateSchema' smart constructor.
data CreateSchema = CreateSchema'
  { -- | A description of the schema.
    CreateSchema -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Tags associated with the schema.
    CreateSchema -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the registry.
    CreateSchema -> Text
registryName :: Prelude.Text,
    -- | The name of the schema.
    CreateSchema -> Text
schemaName :: Prelude.Text,
    -- | The type of schema.
    CreateSchema -> Type
type' :: Type,
    -- | The source of the schema definition.
    CreateSchema -> Text
content :: Prelude.Text
  }
  deriving (CreateSchema -> CreateSchema -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSchema -> CreateSchema -> Bool
$c/= :: CreateSchema -> CreateSchema -> Bool
== :: CreateSchema -> CreateSchema -> Bool
$c== :: CreateSchema -> CreateSchema -> Bool
Prelude.Eq, ReadPrec [CreateSchema]
ReadPrec CreateSchema
Int -> ReadS CreateSchema
ReadS [CreateSchema]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSchema]
$creadListPrec :: ReadPrec [CreateSchema]
readPrec :: ReadPrec CreateSchema
$creadPrec :: ReadPrec CreateSchema
readList :: ReadS [CreateSchema]
$creadList :: ReadS [CreateSchema]
readsPrec :: Int -> ReadS CreateSchema
$creadsPrec :: Int -> ReadS CreateSchema
Prelude.Read, Int -> CreateSchema -> ShowS
[CreateSchema] -> ShowS
CreateSchema -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSchema] -> ShowS
$cshowList :: [CreateSchema] -> ShowS
show :: CreateSchema -> String
$cshow :: CreateSchema -> String
showsPrec :: Int -> CreateSchema -> ShowS
$cshowsPrec :: Int -> CreateSchema -> ShowS
Prelude.Show, forall x. Rep CreateSchema x -> CreateSchema
forall x. CreateSchema -> Rep CreateSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSchema x -> CreateSchema
$cfrom :: forall x. CreateSchema -> Rep CreateSchema x
Prelude.Generic)

-- |
-- Create a value of 'CreateSchema' 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:
--
-- 'description', 'createSchema_description' - A description of the schema.
--
-- 'tags', 'createSchema_tags' - Tags associated with the schema.
--
-- 'registryName', 'createSchema_registryName' - The name of the registry.
--
-- 'schemaName', 'createSchema_schemaName' - The name of the schema.
--
-- 'type'', 'createSchema_type' - The type of schema.
--
-- 'content', 'createSchema_content' - The source of the schema definition.
newCreateSchema ::
  -- | 'registryName'
  Prelude.Text ->
  -- | 'schemaName'
  Prelude.Text ->
  -- | 'type''
  Type ->
  -- | 'content'
  Prelude.Text ->
  CreateSchema
newCreateSchema :: Text -> Text -> Type -> Text -> CreateSchema
newCreateSchema
  Text
pRegistryName_
  Text
pSchemaName_
  Type
pType_
  Text
pContent_ =
    CreateSchema'
      { $sel:description:CreateSchema' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateSchema' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:registryName:CreateSchema' :: Text
registryName = Text
pRegistryName_,
        $sel:schemaName:CreateSchema' :: Text
schemaName = Text
pSchemaName_,
        $sel:type':CreateSchema' :: Type
type' = Type
pType_,
        $sel:content:CreateSchema' :: Text
content = Text
pContent_
      }

-- | A description of the schema.
createSchema_description :: Lens.Lens' CreateSchema (Prelude.Maybe Prelude.Text)
createSchema_description :: Lens' CreateSchema (Maybe Text)
createSchema_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchema' {Maybe Text
description :: Maybe Text
$sel:description:CreateSchema' :: CreateSchema -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateSchema
s@CreateSchema' {} Maybe Text
a -> CreateSchema
s {$sel:description:CreateSchema' :: Maybe Text
description = Maybe Text
a} :: CreateSchema)

-- | Tags associated with the schema.
createSchema_tags :: Lens.Lens' CreateSchema (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createSchema_tags :: Lens' CreateSchema (Maybe (HashMap Text Text))
createSchema_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchema' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateSchema' :: CreateSchema -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateSchema
s@CreateSchema' {} Maybe (HashMap Text Text)
a -> CreateSchema
s {$sel:tags:CreateSchema' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateSchema) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name of the registry.
createSchema_registryName :: Lens.Lens' CreateSchema Prelude.Text
createSchema_registryName :: Lens' CreateSchema Text
createSchema_registryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchema' {Text
registryName :: Text
$sel:registryName:CreateSchema' :: CreateSchema -> Text
registryName} -> Text
registryName) (\s :: CreateSchema
s@CreateSchema' {} Text
a -> CreateSchema
s {$sel:registryName:CreateSchema' :: Text
registryName = Text
a} :: CreateSchema)

-- | The name of the schema.
createSchema_schemaName :: Lens.Lens' CreateSchema Prelude.Text
createSchema_schemaName :: Lens' CreateSchema Text
createSchema_schemaName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchema' {Text
schemaName :: Text
$sel:schemaName:CreateSchema' :: CreateSchema -> Text
schemaName} -> Text
schemaName) (\s :: CreateSchema
s@CreateSchema' {} Text
a -> CreateSchema
s {$sel:schemaName:CreateSchema' :: Text
schemaName = Text
a} :: CreateSchema)

-- | The type of schema.
createSchema_type :: Lens.Lens' CreateSchema Type
createSchema_type :: Lens' CreateSchema Type
createSchema_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchema' {Type
type' :: Type
$sel:type':CreateSchema' :: CreateSchema -> Type
type'} -> Type
type') (\s :: CreateSchema
s@CreateSchema' {} Type
a -> CreateSchema
s {$sel:type':CreateSchema' :: Type
type' = Type
a} :: CreateSchema)

-- | The source of the schema definition.
createSchema_content :: Lens.Lens' CreateSchema Prelude.Text
createSchema_content :: Lens' CreateSchema Text
createSchema_content = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchema' {Text
content :: Text
$sel:content:CreateSchema' :: CreateSchema -> Text
content} -> Text
content) (\s :: CreateSchema
s@CreateSchema' {} Text
a -> CreateSchema
s {$sel:content:CreateSchema' :: Text
content = Text
a} :: CreateSchema)

instance Core.AWSRequest CreateSchema where
  type AWSResponse CreateSchema = CreateSchemaResponse
  request :: (Service -> Service) -> CreateSchema -> Request CreateSchema
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 CreateSchema
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateSchema)))
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
-> Maybe ISO8601
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe ISO8601
-> Int
-> CreateSchemaResponse
CreateSchemaResponse'
            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
"Description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LastModified")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SchemaArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SchemaName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SchemaVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => 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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VersionCreatedDate")
            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 CreateSchema where
  hashWithSalt :: Int -> CreateSchema -> Int
hashWithSalt Int
_salt CreateSchema' {Maybe Text
Maybe (HashMap Text Text)
Text
Type
content :: Text
type' :: Type
schemaName :: Text
registryName :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:content:CreateSchema' :: CreateSchema -> Text
$sel:type':CreateSchema' :: CreateSchema -> Type
$sel:schemaName:CreateSchema' :: CreateSchema -> Text
$sel:registryName:CreateSchema' :: CreateSchema -> Text
$sel:tags:CreateSchema' :: CreateSchema -> Maybe (HashMap Text Text)
$sel:description:CreateSchema' :: CreateSchema -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
registryName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
schemaName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Type
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
content

instance Prelude.NFData CreateSchema where
  rnf :: CreateSchema -> ()
rnf CreateSchema' {Maybe Text
Maybe (HashMap Text Text)
Text
Type
content :: Text
type' :: Type
schemaName :: Text
registryName :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:content:CreateSchema' :: CreateSchema -> Text
$sel:type':CreateSchema' :: CreateSchema -> Type
$sel:schemaName:CreateSchema' :: CreateSchema -> Text
$sel:registryName:CreateSchema' :: CreateSchema -> Text
$sel:tags:CreateSchema' :: CreateSchema -> Maybe (HashMap Text Text)
$sel:description:CreateSchema' :: CreateSchema -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
registryName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
schemaName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Type
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
content

instance Data.ToHeaders CreateSchema where
  toHeaders :: CreateSchema -> 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 CreateSchema where
  toJSON :: CreateSchema -> Value
toJSON CreateSchema' {Maybe Text
Maybe (HashMap Text Text)
Text
Type
content :: Text
type' :: Type
schemaName :: Text
registryName :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:content:CreateSchema' :: CreateSchema -> Text
$sel:type':CreateSchema' :: CreateSchema -> Type
$sel:schemaName:CreateSchema' :: CreateSchema -> Text
$sel:registryName:CreateSchema' :: CreateSchema -> Text
$sel:tags:CreateSchema' :: CreateSchema -> Maybe (HashMap Text Text)
$sel:description:CreateSchema' :: CreateSchema -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (Key
"tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Type
type'),
            forall a. a -> Maybe a
Prelude.Just (Key
"Content" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
content)
          ]
      )

instance Data.ToPath CreateSchema where
  toPath :: CreateSchema -> ByteString
toPath CreateSchema' {Maybe Text
Maybe (HashMap Text Text)
Text
Type
content :: Text
type' :: Type
schemaName :: Text
registryName :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:content:CreateSchema' :: CreateSchema -> Text
$sel:type':CreateSchema' :: CreateSchema -> Type
$sel:schemaName:CreateSchema' :: CreateSchema -> Text
$sel:registryName:CreateSchema' :: CreateSchema -> Text
$sel:tags:CreateSchema' :: CreateSchema -> Maybe (HashMap Text Text)
$sel:description:CreateSchema' :: CreateSchema -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/registries/name/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
registryName,
        ByteString
"/schemas/name/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
schemaName
      ]

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

-- | /See:/ 'newCreateSchemaResponse' smart constructor.
data CreateSchemaResponse = CreateSchemaResponse'
  { -- | The description of the schema.
    CreateSchemaResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The date and time that schema was modified.
    CreateSchemaResponse -> Maybe ISO8601
lastModified :: Prelude.Maybe Data.ISO8601,
    -- | The ARN of the schema.
    CreateSchemaResponse -> Maybe Text
schemaArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the schema.
    CreateSchemaResponse -> Maybe Text
schemaName :: Prelude.Maybe Prelude.Text,
    -- | The version number of the schema
    CreateSchemaResponse -> Maybe Text
schemaVersion :: Prelude.Maybe Prelude.Text,
    CreateSchemaResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The type of the schema.
    CreateSchemaResponse -> Maybe Text
type' :: Prelude.Maybe Prelude.Text,
    -- | The date the schema version was created.
    CreateSchemaResponse -> Maybe ISO8601
versionCreatedDate :: Prelude.Maybe Data.ISO8601,
    -- | The response's http status code.
    CreateSchemaResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateSchemaResponse -> CreateSchemaResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSchemaResponse -> CreateSchemaResponse -> Bool
$c/= :: CreateSchemaResponse -> CreateSchemaResponse -> Bool
== :: CreateSchemaResponse -> CreateSchemaResponse -> Bool
$c== :: CreateSchemaResponse -> CreateSchemaResponse -> Bool
Prelude.Eq, ReadPrec [CreateSchemaResponse]
ReadPrec CreateSchemaResponse
Int -> ReadS CreateSchemaResponse
ReadS [CreateSchemaResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSchemaResponse]
$creadListPrec :: ReadPrec [CreateSchemaResponse]
readPrec :: ReadPrec CreateSchemaResponse
$creadPrec :: ReadPrec CreateSchemaResponse
readList :: ReadS [CreateSchemaResponse]
$creadList :: ReadS [CreateSchemaResponse]
readsPrec :: Int -> ReadS CreateSchemaResponse
$creadsPrec :: Int -> ReadS CreateSchemaResponse
Prelude.Read, Int -> CreateSchemaResponse -> ShowS
[CreateSchemaResponse] -> ShowS
CreateSchemaResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSchemaResponse] -> ShowS
$cshowList :: [CreateSchemaResponse] -> ShowS
show :: CreateSchemaResponse -> String
$cshow :: CreateSchemaResponse -> String
showsPrec :: Int -> CreateSchemaResponse -> ShowS
$cshowsPrec :: Int -> CreateSchemaResponse -> ShowS
Prelude.Show, forall x. Rep CreateSchemaResponse x -> CreateSchemaResponse
forall x. CreateSchemaResponse -> Rep CreateSchemaResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSchemaResponse x -> CreateSchemaResponse
$cfrom :: forall x. CreateSchemaResponse -> Rep CreateSchemaResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateSchemaResponse' 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:
--
-- 'description', 'createSchemaResponse_description' - The description of the schema.
--
-- 'lastModified', 'createSchemaResponse_lastModified' - The date and time that schema was modified.
--
-- 'schemaArn', 'createSchemaResponse_schemaArn' - The ARN of the schema.
--
-- 'schemaName', 'createSchemaResponse_schemaName' - The name of the schema.
--
-- 'schemaVersion', 'createSchemaResponse_schemaVersion' - The version number of the schema
--
-- 'tags', 'createSchemaResponse_tags' - Undocumented member.
--
-- 'type'', 'createSchemaResponse_type' - The type of the schema.
--
-- 'versionCreatedDate', 'createSchemaResponse_versionCreatedDate' - The date the schema version was created.
--
-- 'httpStatus', 'createSchemaResponse_httpStatus' - The response's http status code.
newCreateSchemaResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateSchemaResponse
newCreateSchemaResponse :: Int -> CreateSchemaResponse
newCreateSchemaResponse Int
pHttpStatus_ =
  CreateSchemaResponse'
    { $sel:description:CreateSchemaResponse' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:lastModified:CreateSchemaResponse' :: Maybe ISO8601
lastModified = forall a. Maybe a
Prelude.Nothing,
      $sel:schemaArn:CreateSchemaResponse' :: Maybe Text
schemaArn = forall a. Maybe a
Prelude.Nothing,
      $sel:schemaName:CreateSchemaResponse' :: Maybe Text
schemaName = forall a. Maybe a
Prelude.Nothing,
      $sel:schemaVersion:CreateSchemaResponse' :: Maybe Text
schemaVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateSchemaResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:type':CreateSchemaResponse' :: Maybe Text
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:versionCreatedDate:CreateSchemaResponse' :: Maybe ISO8601
versionCreatedDate = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateSchemaResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The description of the schema.
createSchemaResponse_description :: Lens.Lens' CreateSchemaResponse (Prelude.Maybe Prelude.Text)
createSchemaResponse_description :: Lens' CreateSchemaResponse (Maybe Text)
createSchemaResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchemaResponse' {Maybe Text
description :: Maybe Text
$sel:description:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateSchemaResponse
s@CreateSchemaResponse' {} Maybe Text
a -> CreateSchemaResponse
s {$sel:description:CreateSchemaResponse' :: Maybe Text
description = Maybe Text
a} :: CreateSchemaResponse)

-- | The date and time that schema was modified.
createSchemaResponse_lastModified :: Lens.Lens' CreateSchemaResponse (Prelude.Maybe Prelude.UTCTime)
createSchemaResponse_lastModified :: Lens' CreateSchemaResponse (Maybe UTCTime)
createSchemaResponse_lastModified = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchemaResponse' {Maybe ISO8601
lastModified :: Maybe ISO8601
$sel:lastModified:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe ISO8601
lastModified} -> Maybe ISO8601
lastModified) (\s :: CreateSchemaResponse
s@CreateSchemaResponse' {} Maybe ISO8601
a -> CreateSchemaResponse
s {$sel:lastModified:CreateSchemaResponse' :: Maybe ISO8601
lastModified = Maybe ISO8601
a} :: CreateSchemaResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The ARN of the schema.
createSchemaResponse_schemaArn :: Lens.Lens' CreateSchemaResponse (Prelude.Maybe Prelude.Text)
createSchemaResponse_schemaArn :: Lens' CreateSchemaResponse (Maybe Text)
createSchemaResponse_schemaArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchemaResponse' {Maybe Text
schemaArn :: Maybe Text
$sel:schemaArn:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
schemaArn} -> Maybe Text
schemaArn) (\s :: CreateSchemaResponse
s@CreateSchemaResponse' {} Maybe Text
a -> CreateSchemaResponse
s {$sel:schemaArn:CreateSchemaResponse' :: Maybe Text
schemaArn = Maybe Text
a} :: CreateSchemaResponse)

-- | The name of the schema.
createSchemaResponse_schemaName :: Lens.Lens' CreateSchemaResponse (Prelude.Maybe Prelude.Text)
createSchemaResponse_schemaName :: Lens' CreateSchemaResponse (Maybe Text)
createSchemaResponse_schemaName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchemaResponse' {Maybe Text
schemaName :: Maybe Text
$sel:schemaName:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
schemaName} -> Maybe Text
schemaName) (\s :: CreateSchemaResponse
s@CreateSchemaResponse' {} Maybe Text
a -> CreateSchemaResponse
s {$sel:schemaName:CreateSchemaResponse' :: Maybe Text
schemaName = Maybe Text
a} :: CreateSchemaResponse)

-- | The version number of the schema
createSchemaResponse_schemaVersion :: Lens.Lens' CreateSchemaResponse (Prelude.Maybe Prelude.Text)
createSchemaResponse_schemaVersion :: Lens' CreateSchemaResponse (Maybe Text)
createSchemaResponse_schemaVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchemaResponse' {Maybe Text
schemaVersion :: Maybe Text
$sel:schemaVersion:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
schemaVersion} -> Maybe Text
schemaVersion) (\s :: CreateSchemaResponse
s@CreateSchemaResponse' {} Maybe Text
a -> CreateSchemaResponse
s {$sel:schemaVersion:CreateSchemaResponse' :: Maybe Text
schemaVersion = Maybe Text
a} :: CreateSchemaResponse)

-- | Undocumented member.
createSchemaResponse_tags :: Lens.Lens' CreateSchemaResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createSchemaResponse_tags :: Lens' CreateSchemaResponse (Maybe (HashMap Text Text))
createSchemaResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchemaResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateSchemaResponse
s@CreateSchemaResponse' {} Maybe (HashMap Text Text)
a -> CreateSchemaResponse
s {$sel:tags:CreateSchemaResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateSchemaResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The type of the schema.
createSchemaResponse_type :: Lens.Lens' CreateSchemaResponse (Prelude.Maybe Prelude.Text)
createSchemaResponse_type :: Lens' CreateSchemaResponse (Maybe Text)
createSchemaResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchemaResponse' {Maybe Text
type' :: Maybe Text
$sel:type':CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
type'} -> Maybe Text
type') (\s :: CreateSchemaResponse
s@CreateSchemaResponse' {} Maybe Text
a -> CreateSchemaResponse
s {$sel:type':CreateSchemaResponse' :: Maybe Text
type' = Maybe Text
a} :: CreateSchemaResponse)

-- | The date the schema version was created.
createSchemaResponse_versionCreatedDate :: Lens.Lens' CreateSchemaResponse (Prelude.Maybe Prelude.UTCTime)
createSchemaResponse_versionCreatedDate :: Lens' CreateSchemaResponse (Maybe UTCTime)
createSchemaResponse_versionCreatedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSchemaResponse' {Maybe ISO8601
versionCreatedDate :: Maybe ISO8601
$sel:versionCreatedDate:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe ISO8601
versionCreatedDate} -> Maybe ISO8601
versionCreatedDate) (\s :: CreateSchemaResponse
s@CreateSchemaResponse' {} Maybe ISO8601
a -> CreateSchemaResponse
s {$sel:versionCreatedDate:CreateSchemaResponse' :: Maybe ISO8601
versionCreatedDate = Maybe ISO8601
a} :: CreateSchemaResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

instance Prelude.NFData CreateSchemaResponse where
  rnf :: CreateSchemaResponse -> ()
rnf CreateSchemaResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
httpStatus :: Int
versionCreatedDate :: Maybe ISO8601
type' :: Maybe Text
tags :: Maybe (HashMap Text Text)
schemaVersion :: Maybe Text
schemaName :: Maybe Text
schemaArn :: Maybe Text
lastModified :: Maybe ISO8601
description :: Maybe Text
$sel:httpStatus:CreateSchemaResponse' :: CreateSchemaResponse -> Int
$sel:versionCreatedDate:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe ISO8601
$sel:type':CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
$sel:tags:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe (HashMap Text Text)
$sel:schemaVersion:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
$sel:schemaName:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
$sel:schemaArn:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
$sel:lastModified:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe ISO8601
$sel:description:CreateSchemaResponse' :: CreateSchemaResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
lastModified
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
schemaArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
schemaName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
schemaVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
versionCreatedDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus