{-# 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.IoTEvents.StartDetectorModelAnalysis
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Performs an analysis of your detector model. For more information, see
-- <https://docs.aws.amazon.com/iotevents/latest/developerguide/iotevents-analyze-api.html Troubleshooting a detector model>
-- in the /AWS IoT Events Developer Guide/.
module Amazonka.IoTEvents.StartDetectorModelAnalysis
  ( -- * Creating a Request
    StartDetectorModelAnalysis (..),
    newStartDetectorModelAnalysis,

    -- * Request Lenses
    startDetectorModelAnalysis_detectorModelDefinition,

    -- * Destructuring the Response
    StartDetectorModelAnalysisResponse (..),
    newStartDetectorModelAnalysisResponse,

    -- * Response Lenses
    startDetectorModelAnalysisResponse_analysisId,
    startDetectorModelAnalysisResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'StartDetectorModelAnalysis' 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:
--
-- 'detectorModelDefinition', 'startDetectorModelAnalysis_detectorModelDefinition' - Undocumented member.
newStartDetectorModelAnalysis ::
  -- | 'detectorModelDefinition'
  DetectorModelDefinition ->
  StartDetectorModelAnalysis
newStartDetectorModelAnalysis :: DetectorModelDefinition -> StartDetectorModelAnalysis
newStartDetectorModelAnalysis
  DetectorModelDefinition
pDetectorModelDefinition_ =
    StartDetectorModelAnalysis'
      { $sel:detectorModelDefinition:StartDetectorModelAnalysis' :: DetectorModelDefinition
detectorModelDefinition =
          DetectorModelDefinition
pDetectorModelDefinition_
      }

-- | Undocumented member.
startDetectorModelAnalysis_detectorModelDefinition :: Lens.Lens' StartDetectorModelAnalysis DetectorModelDefinition
startDetectorModelAnalysis_detectorModelDefinition :: Lens' StartDetectorModelAnalysis DetectorModelDefinition
startDetectorModelAnalysis_detectorModelDefinition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDetectorModelAnalysis' {DetectorModelDefinition
detectorModelDefinition :: DetectorModelDefinition
$sel:detectorModelDefinition:StartDetectorModelAnalysis' :: StartDetectorModelAnalysis -> DetectorModelDefinition
detectorModelDefinition} -> DetectorModelDefinition
detectorModelDefinition) (\s :: StartDetectorModelAnalysis
s@StartDetectorModelAnalysis' {} DetectorModelDefinition
a -> StartDetectorModelAnalysis
s {$sel:detectorModelDefinition:StartDetectorModelAnalysis' :: DetectorModelDefinition
detectorModelDefinition = DetectorModelDefinition
a} :: StartDetectorModelAnalysis)

instance Core.AWSRequest StartDetectorModelAnalysis where
  type
    AWSResponse StartDetectorModelAnalysis =
      StartDetectorModelAnalysisResponse
  request :: (Service -> Service)
-> StartDetectorModelAnalysis -> Request StartDetectorModelAnalysis
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 StartDetectorModelAnalysis
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartDetectorModelAnalysis)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> StartDetectorModelAnalysisResponse
StartDetectorModelAnalysisResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"analysisId")
            forall (f :: * -> *) a b. Applicative f => 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 StartDetectorModelAnalysis where
  hashWithSalt :: Int -> StartDetectorModelAnalysis -> Int
hashWithSalt Int
_salt StartDetectorModelAnalysis' {DetectorModelDefinition
detectorModelDefinition :: DetectorModelDefinition
$sel:detectorModelDefinition:StartDetectorModelAnalysis' :: StartDetectorModelAnalysis -> DetectorModelDefinition
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DetectorModelDefinition
detectorModelDefinition

instance Prelude.NFData StartDetectorModelAnalysis where
  rnf :: StartDetectorModelAnalysis -> ()
rnf StartDetectorModelAnalysis' {DetectorModelDefinition
detectorModelDefinition :: DetectorModelDefinition
$sel:detectorModelDefinition:StartDetectorModelAnalysis' :: StartDetectorModelAnalysis -> DetectorModelDefinition
..} =
    forall a. NFData a => a -> ()
Prelude.rnf DetectorModelDefinition
detectorModelDefinition

instance Data.ToHeaders StartDetectorModelAnalysis where
  toHeaders :: StartDetectorModelAnalysis -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON StartDetectorModelAnalysis where
  toJSON :: StartDetectorModelAnalysis -> Value
toJSON StartDetectorModelAnalysis' {DetectorModelDefinition
detectorModelDefinition :: DetectorModelDefinition
$sel:detectorModelDefinition:StartDetectorModelAnalysis' :: StartDetectorModelAnalysis -> DetectorModelDefinition
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"detectorModelDefinition"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= DetectorModelDefinition
detectorModelDefinition
              )
          ]
      )

instance Data.ToPath StartDetectorModelAnalysis where
  toPath :: StartDetectorModelAnalysis -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/analysis/detector-models/"

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

-- | /See:/ 'newStartDetectorModelAnalysisResponse' smart constructor.
data StartDetectorModelAnalysisResponse = StartDetectorModelAnalysisResponse'
  { -- | The ID that you can use to retrieve the analysis result.
    StartDetectorModelAnalysisResponse -> Maybe Text
analysisId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartDetectorModelAnalysisResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartDetectorModelAnalysisResponse
-> StartDetectorModelAnalysisResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartDetectorModelAnalysisResponse
-> StartDetectorModelAnalysisResponse -> Bool
$c/= :: StartDetectorModelAnalysisResponse
-> StartDetectorModelAnalysisResponse -> Bool
== :: StartDetectorModelAnalysisResponse
-> StartDetectorModelAnalysisResponse -> Bool
$c== :: StartDetectorModelAnalysisResponse
-> StartDetectorModelAnalysisResponse -> Bool
Prelude.Eq, ReadPrec [StartDetectorModelAnalysisResponse]
ReadPrec StartDetectorModelAnalysisResponse
Int -> ReadS StartDetectorModelAnalysisResponse
ReadS [StartDetectorModelAnalysisResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartDetectorModelAnalysisResponse]
$creadListPrec :: ReadPrec [StartDetectorModelAnalysisResponse]
readPrec :: ReadPrec StartDetectorModelAnalysisResponse
$creadPrec :: ReadPrec StartDetectorModelAnalysisResponse
readList :: ReadS [StartDetectorModelAnalysisResponse]
$creadList :: ReadS [StartDetectorModelAnalysisResponse]
readsPrec :: Int -> ReadS StartDetectorModelAnalysisResponse
$creadsPrec :: Int -> ReadS StartDetectorModelAnalysisResponse
Prelude.Read, Int -> StartDetectorModelAnalysisResponse -> ShowS
[StartDetectorModelAnalysisResponse] -> ShowS
StartDetectorModelAnalysisResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartDetectorModelAnalysisResponse] -> ShowS
$cshowList :: [StartDetectorModelAnalysisResponse] -> ShowS
show :: StartDetectorModelAnalysisResponse -> String
$cshow :: StartDetectorModelAnalysisResponse -> String
showsPrec :: Int -> StartDetectorModelAnalysisResponse -> ShowS
$cshowsPrec :: Int -> StartDetectorModelAnalysisResponse -> ShowS
Prelude.Show, forall x.
Rep StartDetectorModelAnalysisResponse x
-> StartDetectorModelAnalysisResponse
forall x.
StartDetectorModelAnalysisResponse
-> Rep StartDetectorModelAnalysisResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartDetectorModelAnalysisResponse x
-> StartDetectorModelAnalysisResponse
$cfrom :: forall x.
StartDetectorModelAnalysisResponse
-> Rep StartDetectorModelAnalysisResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartDetectorModelAnalysisResponse' 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:
--
-- 'analysisId', 'startDetectorModelAnalysisResponse_analysisId' - The ID that you can use to retrieve the analysis result.
--
-- 'httpStatus', 'startDetectorModelAnalysisResponse_httpStatus' - The response's http status code.
newStartDetectorModelAnalysisResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartDetectorModelAnalysisResponse
newStartDetectorModelAnalysisResponse :: Int -> StartDetectorModelAnalysisResponse
newStartDetectorModelAnalysisResponse Int
pHttpStatus_ =
  StartDetectorModelAnalysisResponse'
    { $sel:analysisId:StartDetectorModelAnalysisResponse' :: Maybe Text
analysisId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartDetectorModelAnalysisResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID that you can use to retrieve the analysis result.
startDetectorModelAnalysisResponse_analysisId :: Lens.Lens' StartDetectorModelAnalysisResponse (Prelude.Maybe Prelude.Text)
startDetectorModelAnalysisResponse_analysisId :: Lens' StartDetectorModelAnalysisResponse (Maybe Text)
startDetectorModelAnalysisResponse_analysisId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDetectorModelAnalysisResponse' {Maybe Text
analysisId :: Maybe Text
$sel:analysisId:StartDetectorModelAnalysisResponse' :: StartDetectorModelAnalysisResponse -> Maybe Text
analysisId} -> Maybe Text
analysisId) (\s :: StartDetectorModelAnalysisResponse
s@StartDetectorModelAnalysisResponse' {} Maybe Text
a -> StartDetectorModelAnalysisResponse
s {$sel:analysisId:StartDetectorModelAnalysisResponse' :: Maybe Text
analysisId = Maybe Text
a} :: StartDetectorModelAnalysisResponse)

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

instance
  Prelude.NFData
    StartDetectorModelAnalysisResponse
  where
  rnf :: StartDetectorModelAnalysisResponse -> ()
rnf StartDetectorModelAnalysisResponse' {Int
Maybe Text
httpStatus :: Int
analysisId :: Maybe Text
$sel:httpStatus:StartDetectorModelAnalysisResponse' :: StartDetectorModelAnalysisResponse -> Int
$sel:analysisId:StartDetectorModelAnalysisResponse' :: StartDetectorModelAnalysisResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
analysisId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus