{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.KinesisAnalyticsV2.Types.CodeContentDescription
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.KinesisAnalyticsV2.Types.CodeContentDescription where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KinesisAnalyticsV2.Types.S3ApplicationCodeLocationDescription
import qualified Amazonka.Prelude as Prelude

-- | Describes details about the code of a Kinesis Data Analytics
-- application.
--
-- /See:/ 'newCodeContentDescription' smart constructor.
data CodeContentDescription = CodeContentDescription'
  { -- | The checksum that can be used to validate zip-format code.
    CodeContentDescription -> Maybe Text
codeMD5 :: Prelude.Maybe Prelude.Text,
    -- | The size in bytes of the application code. Can be used to validate
    -- zip-format code.
    CodeContentDescription -> Maybe Natural
codeSize :: Prelude.Maybe Prelude.Natural,
    -- | The S3 bucket Amazon Resource Name (ARN), file key, and object version
    -- of the application code stored in Amazon S3.
    CodeContentDescription
-> Maybe S3ApplicationCodeLocationDescription
s3ApplicationCodeLocationDescription :: Prelude.Maybe S3ApplicationCodeLocationDescription,
    -- | The text-format code
    CodeContentDescription -> Maybe Text
textContent :: Prelude.Maybe Prelude.Text
  }
  deriving (CodeContentDescription -> CodeContentDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeContentDescription -> CodeContentDescription -> Bool
$c/= :: CodeContentDescription -> CodeContentDescription -> Bool
== :: CodeContentDescription -> CodeContentDescription -> Bool
$c== :: CodeContentDescription -> CodeContentDescription -> Bool
Prelude.Eq, ReadPrec [CodeContentDescription]
ReadPrec CodeContentDescription
Int -> ReadS CodeContentDescription
ReadS [CodeContentDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CodeContentDescription]
$creadListPrec :: ReadPrec [CodeContentDescription]
readPrec :: ReadPrec CodeContentDescription
$creadPrec :: ReadPrec CodeContentDescription
readList :: ReadS [CodeContentDescription]
$creadList :: ReadS [CodeContentDescription]
readsPrec :: Int -> ReadS CodeContentDescription
$creadsPrec :: Int -> ReadS CodeContentDescription
Prelude.Read, Int -> CodeContentDescription -> ShowS
[CodeContentDescription] -> ShowS
CodeContentDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeContentDescription] -> ShowS
$cshowList :: [CodeContentDescription] -> ShowS
show :: CodeContentDescription -> String
$cshow :: CodeContentDescription -> String
showsPrec :: Int -> CodeContentDescription -> ShowS
$cshowsPrec :: Int -> CodeContentDescription -> ShowS
Prelude.Show, forall x. Rep CodeContentDescription x -> CodeContentDescription
forall x. CodeContentDescription -> Rep CodeContentDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CodeContentDescription x -> CodeContentDescription
$cfrom :: forall x. CodeContentDescription -> Rep CodeContentDescription x
Prelude.Generic)

-- |
-- Create a value of 'CodeContentDescription' 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:
--
-- 'codeMD5', 'codeContentDescription_codeMD5' - The checksum that can be used to validate zip-format code.
--
-- 'codeSize', 'codeContentDescription_codeSize' - The size in bytes of the application code. Can be used to validate
-- zip-format code.
--
-- 's3ApplicationCodeLocationDescription', 'codeContentDescription_s3ApplicationCodeLocationDescription' - The S3 bucket Amazon Resource Name (ARN), file key, and object version
-- of the application code stored in Amazon S3.
--
-- 'textContent', 'codeContentDescription_textContent' - The text-format code
newCodeContentDescription ::
  CodeContentDescription
newCodeContentDescription :: CodeContentDescription
newCodeContentDescription =
  CodeContentDescription'
    { $sel:codeMD5:CodeContentDescription' :: Maybe Text
codeMD5 = forall a. Maybe a
Prelude.Nothing,
      $sel:codeSize:CodeContentDescription' :: Maybe Natural
codeSize = forall a. Maybe a
Prelude.Nothing,
      $sel:s3ApplicationCodeLocationDescription:CodeContentDescription' :: Maybe S3ApplicationCodeLocationDescription
s3ApplicationCodeLocationDescription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:textContent:CodeContentDescription' :: Maybe Text
textContent = forall a. Maybe a
Prelude.Nothing
    }

-- | The checksum that can be used to validate zip-format code.
codeContentDescription_codeMD5 :: Lens.Lens' CodeContentDescription (Prelude.Maybe Prelude.Text)
codeContentDescription_codeMD5 :: Lens' CodeContentDescription (Maybe Text)
codeContentDescription_codeMD5 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CodeContentDescription' {Maybe Text
codeMD5 :: Maybe Text
$sel:codeMD5:CodeContentDescription' :: CodeContentDescription -> Maybe Text
codeMD5} -> Maybe Text
codeMD5) (\s :: CodeContentDescription
s@CodeContentDescription' {} Maybe Text
a -> CodeContentDescription
s {$sel:codeMD5:CodeContentDescription' :: Maybe Text
codeMD5 = Maybe Text
a} :: CodeContentDescription)

-- | The size in bytes of the application code. Can be used to validate
-- zip-format code.
codeContentDescription_codeSize :: Lens.Lens' CodeContentDescription (Prelude.Maybe Prelude.Natural)
codeContentDescription_codeSize :: Lens' CodeContentDescription (Maybe Natural)
codeContentDescription_codeSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CodeContentDescription' {Maybe Natural
codeSize :: Maybe Natural
$sel:codeSize:CodeContentDescription' :: CodeContentDescription -> Maybe Natural
codeSize} -> Maybe Natural
codeSize) (\s :: CodeContentDescription
s@CodeContentDescription' {} Maybe Natural
a -> CodeContentDescription
s {$sel:codeSize:CodeContentDescription' :: Maybe Natural
codeSize = Maybe Natural
a} :: CodeContentDescription)

-- | The S3 bucket Amazon Resource Name (ARN), file key, and object version
-- of the application code stored in Amazon S3.
codeContentDescription_s3ApplicationCodeLocationDescription :: Lens.Lens' CodeContentDescription (Prelude.Maybe S3ApplicationCodeLocationDescription)
codeContentDescription_s3ApplicationCodeLocationDescription :: Lens'
  CodeContentDescription (Maybe S3ApplicationCodeLocationDescription)
codeContentDescription_s3ApplicationCodeLocationDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CodeContentDescription' {Maybe S3ApplicationCodeLocationDescription
s3ApplicationCodeLocationDescription :: Maybe S3ApplicationCodeLocationDescription
$sel:s3ApplicationCodeLocationDescription:CodeContentDescription' :: CodeContentDescription
-> Maybe S3ApplicationCodeLocationDescription
s3ApplicationCodeLocationDescription} -> Maybe S3ApplicationCodeLocationDescription
s3ApplicationCodeLocationDescription) (\s :: CodeContentDescription
s@CodeContentDescription' {} Maybe S3ApplicationCodeLocationDescription
a -> CodeContentDescription
s {$sel:s3ApplicationCodeLocationDescription:CodeContentDescription' :: Maybe S3ApplicationCodeLocationDescription
s3ApplicationCodeLocationDescription = Maybe S3ApplicationCodeLocationDescription
a} :: CodeContentDescription)

-- | The text-format code
codeContentDescription_textContent :: Lens.Lens' CodeContentDescription (Prelude.Maybe Prelude.Text)
codeContentDescription_textContent :: Lens' CodeContentDescription (Maybe Text)
codeContentDescription_textContent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CodeContentDescription' {Maybe Text
textContent :: Maybe Text
$sel:textContent:CodeContentDescription' :: CodeContentDescription -> Maybe Text
textContent} -> Maybe Text
textContent) (\s :: CodeContentDescription
s@CodeContentDescription' {} Maybe Text
a -> CodeContentDescription
s {$sel:textContent:CodeContentDescription' :: Maybe Text
textContent = Maybe Text
a} :: CodeContentDescription)

instance Data.FromJSON CodeContentDescription where
  parseJSON :: Value -> Parser CodeContentDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CodeContentDescription"
      ( \Object
x ->
          Maybe Text
-> Maybe Natural
-> Maybe S3ApplicationCodeLocationDescription
-> Maybe Text
-> CodeContentDescription
CodeContentDescription'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CodeMD5")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CodeSize")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"S3ApplicationCodeLocationDescription")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"TextContent")
      )

instance Prelude.Hashable CodeContentDescription where
  hashWithSalt :: Int -> CodeContentDescription -> Int
hashWithSalt Int
_salt CodeContentDescription' {Maybe Natural
Maybe Text
Maybe S3ApplicationCodeLocationDescription
textContent :: Maybe Text
s3ApplicationCodeLocationDescription :: Maybe S3ApplicationCodeLocationDescription
codeSize :: Maybe Natural
codeMD5 :: Maybe Text
$sel:textContent:CodeContentDescription' :: CodeContentDescription -> Maybe Text
$sel:s3ApplicationCodeLocationDescription:CodeContentDescription' :: CodeContentDescription
-> Maybe S3ApplicationCodeLocationDescription
$sel:codeSize:CodeContentDescription' :: CodeContentDescription -> Maybe Natural
$sel:codeMD5:CodeContentDescription' :: CodeContentDescription -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
codeMD5
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
codeSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe S3ApplicationCodeLocationDescription
s3ApplicationCodeLocationDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
textContent

instance Prelude.NFData CodeContentDescription where
  rnf :: CodeContentDescription -> ()
rnf CodeContentDescription' {Maybe Natural
Maybe Text
Maybe S3ApplicationCodeLocationDescription
textContent :: Maybe Text
s3ApplicationCodeLocationDescription :: Maybe S3ApplicationCodeLocationDescription
codeSize :: Maybe Natural
codeMD5 :: Maybe Text
$sel:textContent:CodeContentDescription' :: CodeContentDescription -> Maybe Text
$sel:s3ApplicationCodeLocationDescription:CodeContentDescription' :: CodeContentDescription
-> Maybe S3ApplicationCodeLocationDescription
$sel:codeSize:CodeContentDescription' :: CodeContentDescription -> Maybe Natural
$sel:codeMD5:CodeContentDescription' :: CodeContentDescription -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
codeMD5
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
codeSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe S3ApplicationCodeLocationDescription
s3ApplicationCodeLocationDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
textContent