{-# 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.LookoutMetrics.BackTestAnomalyDetector
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Runs a backtest for anomaly detection for the specified resource.
module Amazonka.LookoutMetrics.BackTestAnomalyDetector
  ( -- * Creating a Request
    BackTestAnomalyDetector (..),
    newBackTestAnomalyDetector,

    -- * Request Lenses
    backTestAnomalyDetector_anomalyDetectorArn,

    -- * Destructuring the Response
    BackTestAnomalyDetectorResponse (..),
    newBackTestAnomalyDetectorResponse,

    -- * Response Lenses
    backTestAnomalyDetectorResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LookoutMetrics.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newBackTestAnomalyDetector' smart constructor.
data BackTestAnomalyDetector = BackTestAnomalyDetector'
  { -- | The Amazon Resource Name (ARN) of the anomaly detector.
    BackTestAnomalyDetector -> Text
anomalyDetectorArn :: Prelude.Text
  }
  deriving (BackTestAnomalyDetector -> BackTestAnomalyDetector -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BackTestAnomalyDetector -> BackTestAnomalyDetector -> Bool
$c/= :: BackTestAnomalyDetector -> BackTestAnomalyDetector -> Bool
== :: BackTestAnomalyDetector -> BackTestAnomalyDetector -> Bool
$c== :: BackTestAnomalyDetector -> BackTestAnomalyDetector -> Bool
Prelude.Eq, ReadPrec [BackTestAnomalyDetector]
ReadPrec BackTestAnomalyDetector
Int -> ReadS BackTestAnomalyDetector
ReadS [BackTestAnomalyDetector]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BackTestAnomalyDetector]
$creadListPrec :: ReadPrec [BackTestAnomalyDetector]
readPrec :: ReadPrec BackTestAnomalyDetector
$creadPrec :: ReadPrec BackTestAnomalyDetector
readList :: ReadS [BackTestAnomalyDetector]
$creadList :: ReadS [BackTestAnomalyDetector]
readsPrec :: Int -> ReadS BackTestAnomalyDetector
$creadsPrec :: Int -> ReadS BackTestAnomalyDetector
Prelude.Read, Int -> BackTestAnomalyDetector -> ShowS
[BackTestAnomalyDetector] -> ShowS
BackTestAnomalyDetector -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BackTestAnomalyDetector] -> ShowS
$cshowList :: [BackTestAnomalyDetector] -> ShowS
show :: BackTestAnomalyDetector -> String
$cshow :: BackTestAnomalyDetector -> String
showsPrec :: Int -> BackTestAnomalyDetector -> ShowS
$cshowsPrec :: Int -> BackTestAnomalyDetector -> ShowS
Prelude.Show, forall x. Rep BackTestAnomalyDetector x -> BackTestAnomalyDetector
forall x. BackTestAnomalyDetector -> Rep BackTestAnomalyDetector x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BackTestAnomalyDetector x -> BackTestAnomalyDetector
$cfrom :: forall x. BackTestAnomalyDetector -> Rep BackTestAnomalyDetector x
Prelude.Generic)

-- |
-- Create a value of 'BackTestAnomalyDetector' 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:
--
-- 'anomalyDetectorArn', 'backTestAnomalyDetector_anomalyDetectorArn' - The Amazon Resource Name (ARN) of the anomaly detector.
newBackTestAnomalyDetector ::
  -- | 'anomalyDetectorArn'
  Prelude.Text ->
  BackTestAnomalyDetector
newBackTestAnomalyDetector :: Text -> BackTestAnomalyDetector
newBackTestAnomalyDetector Text
pAnomalyDetectorArn_ =
  BackTestAnomalyDetector'
    { $sel:anomalyDetectorArn:BackTestAnomalyDetector' :: Text
anomalyDetectorArn =
        Text
pAnomalyDetectorArn_
    }

-- | The Amazon Resource Name (ARN) of the anomaly detector.
backTestAnomalyDetector_anomalyDetectorArn :: Lens.Lens' BackTestAnomalyDetector Prelude.Text
backTestAnomalyDetector_anomalyDetectorArn :: Lens' BackTestAnomalyDetector Text
backTestAnomalyDetector_anomalyDetectorArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BackTestAnomalyDetector' {Text
anomalyDetectorArn :: Text
$sel:anomalyDetectorArn:BackTestAnomalyDetector' :: BackTestAnomalyDetector -> Text
anomalyDetectorArn} -> Text
anomalyDetectorArn) (\s :: BackTestAnomalyDetector
s@BackTestAnomalyDetector' {} Text
a -> BackTestAnomalyDetector
s {$sel:anomalyDetectorArn:BackTestAnomalyDetector' :: Text
anomalyDetectorArn = Text
a} :: BackTestAnomalyDetector)

instance Core.AWSRequest BackTestAnomalyDetector where
  type
    AWSResponse BackTestAnomalyDetector =
      BackTestAnomalyDetectorResponse
  request :: (Service -> Service)
-> BackTestAnomalyDetector -> Request BackTestAnomalyDetector
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 BackTestAnomalyDetector
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BackTestAnomalyDetector)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> BackTestAnomalyDetectorResponse
BackTestAnomalyDetectorResponse'
            forall (f :: * -> *) a b. Functor 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 BackTestAnomalyDetector where
  hashWithSalt :: Int -> BackTestAnomalyDetector -> Int
hashWithSalt Int
_salt BackTestAnomalyDetector' {Text
anomalyDetectorArn :: Text
$sel:anomalyDetectorArn:BackTestAnomalyDetector' :: BackTestAnomalyDetector -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
anomalyDetectorArn

instance Prelude.NFData BackTestAnomalyDetector where
  rnf :: BackTestAnomalyDetector -> ()
rnf BackTestAnomalyDetector' {Text
anomalyDetectorArn :: Text
$sel:anomalyDetectorArn:BackTestAnomalyDetector' :: BackTestAnomalyDetector -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
anomalyDetectorArn

instance Data.ToHeaders BackTestAnomalyDetector where
  toHeaders :: BackTestAnomalyDetector -> 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 BackTestAnomalyDetector where
  toJSON :: BackTestAnomalyDetector -> Value
toJSON BackTestAnomalyDetector' {Text
anomalyDetectorArn :: Text
$sel:anomalyDetectorArn:BackTestAnomalyDetector' :: BackTestAnomalyDetector -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"AnomalyDetectorArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
anomalyDetectorArn)
          ]
      )

instance Data.ToPath BackTestAnomalyDetector where
  toPath :: BackTestAnomalyDetector -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/BackTestAnomalyDetector"

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

-- | /See:/ 'newBackTestAnomalyDetectorResponse' smart constructor.
data BackTestAnomalyDetectorResponse = BackTestAnomalyDetectorResponse'
  { -- | The response's http status code.
    BackTestAnomalyDetectorResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BackTestAnomalyDetectorResponse
-> BackTestAnomalyDetectorResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BackTestAnomalyDetectorResponse
-> BackTestAnomalyDetectorResponse -> Bool
$c/= :: BackTestAnomalyDetectorResponse
-> BackTestAnomalyDetectorResponse -> Bool
== :: BackTestAnomalyDetectorResponse
-> BackTestAnomalyDetectorResponse -> Bool
$c== :: BackTestAnomalyDetectorResponse
-> BackTestAnomalyDetectorResponse -> Bool
Prelude.Eq, ReadPrec [BackTestAnomalyDetectorResponse]
ReadPrec BackTestAnomalyDetectorResponse
Int -> ReadS BackTestAnomalyDetectorResponse
ReadS [BackTestAnomalyDetectorResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BackTestAnomalyDetectorResponse]
$creadListPrec :: ReadPrec [BackTestAnomalyDetectorResponse]
readPrec :: ReadPrec BackTestAnomalyDetectorResponse
$creadPrec :: ReadPrec BackTestAnomalyDetectorResponse
readList :: ReadS [BackTestAnomalyDetectorResponse]
$creadList :: ReadS [BackTestAnomalyDetectorResponse]
readsPrec :: Int -> ReadS BackTestAnomalyDetectorResponse
$creadsPrec :: Int -> ReadS BackTestAnomalyDetectorResponse
Prelude.Read, Int -> BackTestAnomalyDetectorResponse -> ShowS
[BackTestAnomalyDetectorResponse] -> ShowS
BackTestAnomalyDetectorResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BackTestAnomalyDetectorResponse] -> ShowS
$cshowList :: [BackTestAnomalyDetectorResponse] -> ShowS
show :: BackTestAnomalyDetectorResponse -> String
$cshow :: BackTestAnomalyDetectorResponse -> String
showsPrec :: Int -> BackTestAnomalyDetectorResponse -> ShowS
$cshowsPrec :: Int -> BackTestAnomalyDetectorResponse -> ShowS
Prelude.Show, forall x.
Rep BackTestAnomalyDetectorResponse x
-> BackTestAnomalyDetectorResponse
forall x.
BackTestAnomalyDetectorResponse
-> Rep BackTestAnomalyDetectorResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BackTestAnomalyDetectorResponse x
-> BackTestAnomalyDetectorResponse
$cfrom :: forall x.
BackTestAnomalyDetectorResponse
-> Rep BackTestAnomalyDetectorResponse x
Prelude.Generic)

-- |
-- Create a value of 'BackTestAnomalyDetectorResponse' 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:
--
-- 'httpStatus', 'backTestAnomalyDetectorResponse_httpStatus' - The response's http status code.
newBackTestAnomalyDetectorResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BackTestAnomalyDetectorResponse
newBackTestAnomalyDetectorResponse :: Int -> BackTestAnomalyDetectorResponse
newBackTestAnomalyDetectorResponse Int
pHttpStatus_ =
  BackTestAnomalyDetectorResponse'
    { $sel:httpStatus:BackTestAnomalyDetectorResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    BackTestAnomalyDetectorResponse
  where
  rnf :: BackTestAnomalyDetectorResponse -> ()
rnf BackTestAnomalyDetectorResponse' {Int
httpStatus :: Int
$sel:httpStatus:BackTestAnomalyDetectorResponse' :: BackTestAnomalyDetectorResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus