{-# 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.Pinpoint.Types.InAppMessage
-- 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.Pinpoint.Types.InAppMessage where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Pinpoint.Types.InAppMessageContent
import Amazonka.Pinpoint.Types.Layout
import qualified Amazonka.Prelude as Prelude

-- | Provides all fields required for building an in-app message.
--
-- /See:/ 'newInAppMessage' smart constructor.
data InAppMessage = InAppMessage'
  { -- | In-app message content.
    InAppMessage -> Maybe [InAppMessageContent]
content :: Prelude.Maybe [InAppMessageContent],
    -- | Custom config to be sent to SDK.
    InAppMessage -> Maybe (HashMap Text Text)
customConfig :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The layout of the message.
    InAppMessage -> Maybe Layout
layout :: Prelude.Maybe Layout
  }
  deriving (InAppMessage -> InAppMessage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InAppMessage -> InAppMessage -> Bool
$c/= :: InAppMessage -> InAppMessage -> Bool
== :: InAppMessage -> InAppMessage -> Bool
$c== :: InAppMessage -> InAppMessage -> Bool
Prelude.Eq, ReadPrec [InAppMessage]
ReadPrec InAppMessage
Int -> ReadS InAppMessage
ReadS [InAppMessage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InAppMessage]
$creadListPrec :: ReadPrec [InAppMessage]
readPrec :: ReadPrec InAppMessage
$creadPrec :: ReadPrec InAppMessage
readList :: ReadS [InAppMessage]
$creadList :: ReadS [InAppMessage]
readsPrec :: Int -> ReadS InAppMessage
$creadsPrec :: Int -> ReadS InAppMessage
Prelude.Read, Int -> InAppMessage -> ShowS
[InAppMessage] -> ShowS
InAppMessage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InAppMessage] -> ShowS
$cshowList :: [InAppMessage] -> ShowS
show :: InAppMessage -> String
$cshow :: InAppMessage -> String
showsPrec :: Int -> InAppMessage -> ShowS
$cshowsPrec :: Int -> InAppMessage -> ShowS
Prelude.Show, forall x. Rep InAppMessage x -> InAppMessage
forall x. InAppMessage -> Rep InAppMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InAppMessage x -> InAppMessage
$cfrom :: forall x. InAppMessage -> Rep InAppMessage x
Prelude.Generic)

-- |
-- Create a value of 'InAppMessage' 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:
--
-- 'content', 'inAppMessage_content' - In-app message content.
--
-- 'customConfig', 'inAppMessage_customConfig' - Custom config to be sent to SDK.
--
-- 'layout', 'inAppMessage_layout' - The layout of the message.
newInAppMessage ::
  InAppMessage
newInAppMessage :: InAppMessage
newInAppMessage =
  InAppMessage'
    { $sel:content:InAppMessage' :: Maybe [InAppMessageContent]
content = forall a. Maybe a
Prelude.Nothing,
      $sel:customConfig:InAppMessage' :: Maybe (HashMap Text Text)
customConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:layout:InAppMessage' :: Maybe Layout
layout = forall a. Maybe a
Prelude.Nothing
    }

-- | In-app message content.
inAppMessage_content :: Lens.Lens' InAppMessage (Prelude.Maybe [InAppMessageContent])
inAppMessage_content :: Lens' InAppMessage (Maybe [InAppMessageContent])
inAppMessage_content = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InAppMessage' {Maybe [InAppMessageContent]
content :: Maybe [InAppMessageContent]
$sel:content:InAppMessage' :: InAppMessage -> Maybe [InAppMessageContent]
content} -> Maybe [InAppMessageContent]
content) (\s :: InAppMessage
s@InAppMessage' {} Maybe [InAppMessageContent]
a -> InAppMessage
s {$sel:content:InAppMessage' :: Maybe [InAppMessageContent]
content = Maybe [InAppMessageContent]
a} :: InAppMessage) 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

-- | Custom config to be sent to SDK.
inAppMessage_customConfig :: Lens.Lens' InAppMessage (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
inAppMessage_customConfig :: Lens' InAppMessage (Maybe (HashMap Text Text))
inAppMessage_customConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InAppMessage' {Maybe (HashMap Text Text)
customConfig :: Maybe (HashMap Text Text)
$sel:customConfig:InAppMessage' :: InAppMessage -> Maybe (HashMap Text Text)
customConfig} -> Maybe (HashMap Text Text)
customConfig) (\s :: InAppMessage
s@InAppMessage' {} Maybe (HashMap Text Text)
a -> InAppMessage
s {$sel:customConfig:InAppMessage' :: Maybe (HashMap Text Text)
customConfig = Maybe (HashMap Text Text)
a} :: InAppMessage) 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 layout of the message.
inAppMessage_layout :: Lens.Lens' InAppMessage (Prelude.Maybe Layout)
inAppMessage_layout :: Lens' InAppMessage (Maybe Layout)
inAppMessage_layout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InAppMessage' {Maybe Layout
layout :: Maybe Layout
$sel:layout:InAppMessage' :: InAppMessage -> Maybe Layout
layout} -> Maybe Layout
layout) (\s :: InAppMessage
s@InAppMessage' {} Maybe Layout
a -> InAppMessage
s {$sel:layout:InAppMessage' :: Maybe Layout
layout = Maybe Layout
a} :: InAppMessage)

instance Data.FromJSON InAppMessage where
  parseJSON :: Value -> Parser InAppMessage
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"InAppMessage"
      ( \Object
x ->
          Maybe [InAppMessageContent]
-> Maybe (HashMap Text Text) -> Maybe Layout -> InAppMessage
InAppMessage'
            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
"Content" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"CustomConfig" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"Layout")
      )

instance Prelude.Hashable InAppMessage where
  hashWithSalt :: Int -> InAppMessage -> Int
hashWithSalt Int
_salt InAppMessage' {Maybe [InAppMessageContent]
Maybe (HashMap Text Text)
Maybe Layout
layout :: Maybe Layout
customConfig :: Maybe (HashMap Text Text)
content :: Maybe [InAppMessageContent]
$sel:layout:InAppMessage' :: InAppMessage -> Maybe Layout
$sel:customConfig:InAppMessage' :: InAppMessage -> Maybe (HashMap Text Text)
$sel:content:InAppMessage' :: InAppMessage -> Maybe [InAppMessageContent]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InAppMessageContent]
content
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
customConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Layout
layout

instance Prelude.NFData InAppMessage where
  rnf :: InAppMessage -> ()
rnf InAppMessage' {Maybe [InAppMessageContent]
Maybe (HashMap Text Text)
Maybe Layout
layout :: Maybe Layout
customConfig :: Maybe (HashMap Text Text)
content :: Maybe [InAppMessageContent]
$sel:layout:InAppMessage' :: InAppMessage -> Maybe Layout
$sel:customConfig:InAppMessage' :: InAppMessage -> Maybe (HashMap Text Text)
$sel:content:InAppMessage' :: InAppMessage -> Maybe [InAppMessageContent]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [InAppMessageContent]
content
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
customConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Layout
layout