{-# 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.SQS.Types.MessageSystemAttributeValue
-- 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.SQS.Types.MessageSystemAttributeValue 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

-- | The user-specified message system attribute value. For string data
-- types, the @Value@ attribute has the same restrictions on the content as
-- the message body. For more information, see @ @@SendMessage@@.@
--
-- @Name@, @type@, @value@ and the message body must not be empty or null.
--
-- /See:/ 'newMessageSystemAttributeValue' smart constructor.
data MessageSystemAttributeValue = MessageSystemAttributeValue'
  { -- | Not implemented. Reserved for future use.
    MessageSystemAttributeValue -> Maybe [Base64]
binaryListValues :: Prelude.Maybe [Data.Base64],
    -- | Binary type attributes can store any binary data, such as compressed
    -- data, encrypted data, or images.
    MessageSystemAttributeValue -> Maybe Base64
binaryValue :: Prelude.Maybe Data.Base64,
    -- | Not implemented. Reserved for future use.
    MessageSystemAttributeValue -> Maybe [Text]
stringListValues :: Prelude.Maybe [Prelude.Text],
    -- | Strings are Unicode with UTF-8 binary encoding. For a list of code
    -- values, see
    -- <http://en.wikipedia.org/wiki/ASCII#ASCII_printable_characters ASCII Printable Characters>.
    MessageSystemAttributeValue -> Maybe Text
stringValue :: Prelude.Maybe Prelude.Text,
    -- | Amazon SQS supports the following logical data types: @String@,
    -- @Number@, and @Binary@. For the @Number@ data type, you must use
    -- @StringValue@.
    --
    -- You can also append custom labels. For more information, see
    -- <https://docs.aws.amazon.com/AWSSimpleQueueService/latest/SQSDeveloperGuide/sqs-message-metadata.html#sqs-message-attributes Amazon SQS Message Attributes>
    -- in the /Amazon SQS Developer Guide/.
    MessageSystemAttributeValue -> Text
dataType :: Prelude.Text
  }
  deriving (MessageSystemAttributeValue -> MessageSystemAttributeValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageSystemAttributeValue -> MessageSystemAttributeValue -> Bool
$c/= :: MessageSystemAttributeValue -> MessageSystemAttributeValue -> Bool
== :: MessageSystemAttributeValue -> MessageSystemAttributeValue -> Bool
$c== :: MessageSystemAttributeValue -> MessageSystemAttributeValue -> Bool
Prelude.Eq, ReadPrec [MessageSystemAttributeValue]
ReadPrec MessageSystemAttributeValue
Int -> ReadS MessageSystemAttributeValue
ReadS [MessageSystemAttributeValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MessageSystemAttributeValue]
$creadListPrec :: ReadPrec [MessageSystemAttributeValue]
readPrec :: ReadPrec MessageSystemAttributeValue
$creadPrec :: ReadPrec MessageSystemAttributeValue
readList :: ReadS [MessageSystemAttributeValue]
$creadList :: ReadS [MessageSystemAttributeValue]
readsPrec :: Int -> ReadS MessageSystemAttributeValue
$creadsPrec :: Int -> ReadS MessageSystemAttributeValue
Prelude.Read, Int -> MessageSystemAttributeValue -> ShowS
[MessageSystemAttributeValue] -> ShowS
MessageSystemAttributeValue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageSystemAttributeValue] -> ShowS
$cshowList :: [MessageSystemAttributeValue] -> ShowS
show :: MessageSystemAttributeValue -> String
$cshow :: MessageSystemAttributeValue -> String
showsPrec :: Int -> MessageSystemAttributeValue -> ShowS
$cshowsPrec :: Int -> MessageSystemAttributeValue -> ShowS
Prelude.Show, forall x.
Rep MessageSystemAttributeValue x -> MessageSystemAttributeValue
forall x.
MessageSystemAttributeValue -> Rep MessageSystemAttributeValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep MessageSystemAttributeValue x -> MessageSystemAttributeValue
$cfrom :: forall x.
MessageSystemAttributeValue -> Rep MessageSystemAttributeValue x
Prelude.Generic)

-- |
-- Create a value of 'MessageSystemAttributeValue' 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:
--
-- 'binaryListValues', 'messageSystemAttributeValue_binaryListValues' - Not implemented. Reserved for future use.
--
-- 'binaryValue', 'messageSystemAttributeValue_binaryValue' - Binary type attributes can store any binary data, such as compressed
-- data, encrypted data, or images.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
--
-- 'stringListValues', 'messageSystemAttributeValue_stringListValues' - Not implemented. Reserved for future use.
--
-- 'stringValue', 'messageSystemAttributeValue_stringValue' - Strings are Unicode with UTF-8 binary encoding. For a list of code
-- values, see
-- <http://en.wikipedia.org/wiki/ASCII#ASCII_printable_characters ASCII Printable Characters>.
--
-- 'dataType', 'messageSystemAttributeValue_dataType' - Amazon SQS supports the following logical data types: @String@,
-- @Number@, and @Binary@. For the @Number@ data type, you must use
-- @StringValue@.
--
-- You can also append custom labels. For more information, see
-- <https://docs.aws.amazon.com/AWSSimpleQueueService/latest/SQSDeveloperGuide/sqs-message-metadata.html#sqs-message-attributes Amazon SQS Message Attributes>
-- in the /Amazon SQS Developer Guide/.
newMessageSystemAttributeValue ::
  -- | 'dataType'
  Prelude.Text ->
  MessageSystemAttributeValue
newMessageSystemAttributeValue :: Text -> MessageSystemAttributeValue
newMessageSystemAttributeValue Text
pDataType_ =
  MessageSystemAttributeValue'
    { $sel:binaryListValues:MessageSystemAttributeValue' :: Maybe [Base64]
binaryListValues =
        forall a. Maybe a
Prelude.Nothing,
      $sel:binaryValue:MessageSystemAttributeValue' :: Maybe Base64
binaryValue = forall a. Maybe a
Prelude.Nothing,
      $sel:stringListValues:MessageSystemAttributeValue' :: Maybe [Text]
stringListValues = forall a. Maybe a
Prelude.Nothing,
      $sel:stringValue:MessageSystemAttributeValue' :: Maybe Text
stringValue = forall a. Maybe a
Prelude.Nothing,
      $sel:dataType:MessageSystemAttributeValue' :: Text
dataType = Text
pDataType_
    }

-- | Not implemented. Reserved for future use.
messageSystemAttributeValue_binaryListValues :: Lens.Lens' MessageSystemAttributeValue (Prelude.Maybe [Prelude.ByteString])
messageSystemAttributeValue_binaryListValues :: Lens' MessageSystemAttributeValue (Maybe [ByteString])
messageSystemAttributeValue_binaryListValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MessageSystemAttributeValue' {Maybe [Base64]
binaryListValues :: Maybe [Base64]
$sel:binaryListValues:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe [Base64]
binaryListValues} -> Maybe [Base64]
binaryListValues) (\s :: MessageSystemAttributeValue
s@MessageSystemAttributeValue' {} Maybe [Base64]
a -> MessageSystemAttributeValue
s {$sel:binaryListValues:MessageSystemAttributeValue' :: Maybe [Base64]
binaryListValues = Maybe [Base64]
a} :: MessageSystemAttributeValue) 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

-- | Binary type attributes can store any binary data, such as compressed
-- data, encrypted data, or images.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
messageSystemAttributeValue_binaryValue :: Lens.Lens' MessageSystemAttributeValue (Prelude.Maybe Prelude.ByteString)
messageSystemAttributeValue_binaryValue :: Lens' MessageSystemAttributeValue (Maybe ByteString)
messageSystemAttributeValue_binaryValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MessageSystemAttributeValue' {Maybe Base64
binaryValue :: Maybe Base64
$sel:binaryValue:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe Base64
binaryValue} -> Maybe Base64
binaryValue) (\s :: MessageSystemAttributeValue
s@MessageSystemAttributeValue' {} Maybe Base64
a -> MessageSystemAttributeValue
s {$sel:binaryValue:MessageSystemAttributeValue' :: Maybe Base64
binaryValue = Maybe Base64
a} :: MessageSystemAttributeValue) 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 Iso' Base64 ByteString
Data._Base64

-- | Not implemented. Reserved for future use.
messageSystemAttributeValue_stringListValues :: Lens.Lens' MessageSystemAttributeValue (Prelude.Maybe [Prelude.Text])
messageSystemAttributeValue_stringListValues :: Lens' MessageSystemAttributeValue (Maybe [Text])
messageSystemAttributeValue_stringListValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MessageSystemAttributeValue' {Maybe [Text]
stringListValues :: Maybe [Text]
$sel:stringListValues:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe [Text]
stringListValues} -> Maybe [Text]
stringListValues) (\s :: MessageSystemAttributeValue
s@MessageSystemAttributeValue' {} Maybe [Text]
a -> MessageSystemAttributeValue
s {$sel:stringListValues:MessageSystemAttributeValue' :: Maybe [Text]
stringListValues = Maybe [Text]
a} :: MessageSystemAttributeValue) 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

-- | Strings are Unicode with UTF-8 binary encoding. For a list of code
-- values, see
-- <http://en.wikipedia.org/wiki/ASCII#ASCII_printable_characters ASCII Printable Characters>.
messageSystemAttributeValue_stringValue :: Lens.Lens' MessageSystemAttributeValue (Prelude.Maybe Prelude.Text)
messageSystemAttributeValue_stringValue :: Lens' MessageSystemAttributeValue (Maybe Text)
messageSystemAttributeValue_stringValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MessageSystemAttributeValue' {Maybe Text
stringValue :: Maybe Text
$sel:stringValue:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe Text
stringValue} -> Maybe Text
stringValue) (\s :: MessageSystemAttributeValue
s@MessageSystemAttributeValue' {} Maybe Text
a -> MessageSystemAttributeValue
s {$sel:stringValue:MessageSystemAttributeValue' :: Maybe Text
stringValue = Maybe Text
a} :: MessageSystemAttributeValue)

-- | Amazon SQS supports the following logical data types: @String@,
-- @Number@, and @Binary@. For the @Number@ data type, you must use
-- @StringValue@.
--
-- You can also append custom labels. For more information, see
-- <https://docs.aws.amazon.com/AWSSimpleQueueService/latest/SQSDeveloperGuide/sqs-message-metadata.html#sqs-message-attributes Amazon SQS Message Attributes>
-- in the /Amazon SQS Developer Guide/.
messageSystemAttributeValue_dataType :: Lens.Lens' MessageSystemAttributeValue Prelude.Text
messageSystemAttributeValue_dataType :: Lens' MessageSystemAttributeValue Text
messageSystemAttributeValue_dataType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MessageSystemAttributeValue' {Text
dataType :: Text
$sel:dataType:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Text
dataType} -> Text
dataType) (\s :: MessageSystemAttributeValue
s@MessageSystemAttributeValue' {} Text
a -> MessageSystemAttributeValue
s {$sel:dataType:MessageSystemAttributeValue' :: Text
dataType = Text
a} :: MessageSystemAttributeValue)

instance Prelude.Hashable MessageSystemAttributeValue where
  hashWithSalt :: Int -> MessageSystemAttributeValue -> Int
hashWithSalt Int
_salt MessageSystemAttributeValue' {Maybe [Text]
Maybe [Base64]
Maybe Text
Maybe Base64
Text
dataType :: Text
stringValue :: Maybe Text
stringListValues :: Maybe [Text]
binaryValue :: Maybe Base64
binaryListValues :: Maybe [Base64]
$sel:dataType:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Text
$sel:stringValue:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe Text
$sel:stringListValues:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe [Text]
$sel:binaryValue:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe Base64
$sel:binaryListValues:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe [Base64]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Base64]
binaryListValues
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Base64
binaryValue
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
stringListValues
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stringValue
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dataType

instance Prelude.NFData MessageSystemAttributeValue where
  rnf :: MessageSystemAttributeValue -> ()
rnf MessageSystemAttributeValue' {Maybe [Text]
Maybe [Base64]
Maybe Text
Maybe Base64
Text
dataType :: Text
stringValue :: Maybe Text
stringListValues :: Maybe [Text]
binaryValue :: Maybe Base64
binaryListValues :: Maybe [Base64]
$sel:dataType:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Text
$sel:stringValue:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe Text
$sel:stringListValues:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe [Text]
$sel:binaryValue:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe Base64
$sel:binaryListValues:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe [Base64]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Base64]
binaryListValues
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Base64
binaryValue
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
stringListValues
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stringValue
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dataType

instance Data.ToQuery MessageSystemAttributeValue where
  toQuery :: MessageSystemAttributeValue -> QueryString
toQuery MessageSystemAttributeValue' {Maybe [Text]
Maybe [Base64]
Maybe Text
Maybe Base64
Text
dataType :: Text
stringValue :: Maybe Text
stringListValues :: Maybe [Text]
binaryValue :: Maybe Base64
binaryListValues :: Maybe [Base64]
$sel:dataType:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Text
$sel:stringValue:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe Text
$sel:stringListValues:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe [Text]
$sel:binaryValue:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe Base64
$sel:binaryListValues:MessageSystemAttributeValue' :: MessageSystemAttributeValue -> Maybe [Base64]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"BinaryListValue"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"BinaryListValue"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Base64]
binaryListValues
            ),
        ByteString
"BinaryValue" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Base64
binaryValue,
        ByteString
"StringListValue"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"StringListValue"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
stringListValues
            ),
        ByteString
"StringValue" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
stringValue,
        ByteString
"DataType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dataType
      ]