{-# 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.Rum.Types.DataStorage
-- 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.Rum.Types.DataStorage 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 Amazonka.Rum.Types.CwLog

-- | A structure that contains information about whether this app monitor
-- stores a copy of the telemetry data that RUM collects using CloudWatch
-- Logs.
--
-- /See:/ 'newDataStorage' smart constructor.
data DataStorage = DataStorage'
  { -- | A structure that contains the information about whether the app monitor
    -- stores copies of the data that RUM collects in CloudWatch Logs. If it
    -- does, this structure also contains the name of the log group.
    DataStorage -> Maybe CwLog
cwLog :: Prelude.Maybe CwLog
  }
  deriving (DataStorage -> DataStorage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataStorage -> DataStorage -> Bool
$c/= :: DataStorage -> DataStorage -> Bool
== :: DataStorage -> DataStorage -> Bool
$c== :: DataStorage -> DataStorage -> Bool
Prelude.Eq, ReadPrec [DataStorage]
ReadPrec DataStorage
Int -> ReadS DataStorage
ReadS [DataStorage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataStorage]
$creadListPrec :: ReadPrec [DataStorage]
readPrec :: ReadPrec DataStorage
$creadPrec :: ReadPrec DataStorage
readList :: ReadS [DataStorage]
$creadList :: ReadS [DataStorage]
readsPrec :: Int -> ReadS DataStorage
$creadsPrec :: Int -> ReadS DataStorage
Prelude.Read, Int -> DataStorage -> ShowS
[DataStorage] -> ShowS
DataStorage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataStorage] -> ShowS
$cshowList :: [DataStorage] -> ShowS
show :: DataStorage -> String
$cshow :: DataStorage -> String
showsPrec :: Int -> DataStorage -> ShowS
$cshowsPrec :: Int -> DataStorage -> ShowS
Prelude.Show, forall x. Rep DataStorage x -> DataStorage
forall x. DataStorage -> Rep DataStorage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataStorage x -> DataStorage
$cfrom :: forall x. DataStorage -> Rep DataStorage x
Prelude.Generic)

-- |
-- Create a value of 'DataStorage' 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:
--
-- 'cwLog', 'dataStorage_cwLog' - A structure that contains the information about whether the app monitor
-- stores copies of the data that RUM collects in CloudWatch Logs. If it
-- does, this structure also contains the name of the log group.
newDataStorage ::
  DataStorage
newDataStorage :: DataStorage
newDataStorage =
  DataStorage' {$sel:cwLog:DataStorage' :: Maybe CwLog
cwLog = forall a. Maybe a
Prelude.Nothing}

-- | A structure that contains the information about whether the app monitor
-- stores copies of the data that RUM collects in CloudWatch Logs. If it
-- does, this structure also contains the name of the log group.
dataStorage_cwLog :: Lens.Lens' DataStorage (Prelude.Maybe CwLog)
dataStorage_cwLog :: Lens' DataStorage (Maybe CwLog)
dataStorage_cwLog = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataStorage' {Maybe CwLog
cwLog :: Maybe CwLog
$sel:cwLog:DataStorage' :: DataStorage -> Maybe CwLog
cwLog} -> Maybe CwLog
cwLog) (\s :: DataStorage
s@DataStorage' {} Maybe CwLog
a -> DataStorage
s {$sel:cwLog:DataStorage' :: Maybe CwLog
cwLog = Maybe CwLog
a} :: DataStorage)

instance Data.FromJSON DataStorage where
  parseJSON :: Value -> Parser DataStorage
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DataStorage"
      ( \Object
x ->
          Maybe CwLog -> DataStorage
DataStorage' 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
"CwLog")
      )

instance Prelude.Hashable DataStorage where
  hashWithSalt :: Int -> DataStorage -> Int
hashWithSalt Int
_salt DataStorage' {Maybe CwLog
cwLog :: Maybe CwLog
$sel:cwLog:DataStorage' :: DataStorage -> Maybe CwLog
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CwLog
cwLog

instance Prelude.NFData DataStorage where
  rnf :: DataStorage -> ()
rnf DataStorage' {Maybe CwLog
cwLog :: Maybe CwLog
$sel:cwLog:DataStorage' :: DataStorage -> Maybe CwLog
..} = forall a. NFData a => a -> ()
Prelude.rnf Maybe CwLog
cwLog