{-# 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.GuardDuty.GetDetector
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves an Amazon GuardDuty detector specified by the detectorId.
module Amazonka.GuardDuty.GetDetector
  ( -- * Creating a Request
    GetDetector (..),
    newGetDetector,

    -- * Request Lenses
    getDetector_detectorId,

    -- * Destructuring the Response
    GetDetectorResponse (..),
    newGetDetectorResponse,

    -- * Response Lenses
    getDetectorResponse_createdAt,
    getDetectorResponse_dataSources,
    getDetectorResponse_findingPublishingFrequency,
    getDetectorResponse_tags,
    getDetectorResponse_updatedAt,
    getDetectorResponse_httpStatus,
    getDetectorResponse_serviceRole,
    getDetectorResponse_status,
  )
where

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

-- | /See:/ 'newGetDetector' smart constructor.
data GetDetector = GetDetector'
  { -- | The unique ID of the detector that you want to get.
    GetDetector -> Text
detectorId :: Prelude.Text
  }
  deriving (GetDetector -> GetDetector -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDetector -> GetDetector -> Bool
$c/= :: GetDetector -> GetDetector -> Bool
== :: GetDetector -> GetDetector -> Bool
$c== :: GetDetector -> GetDetector -> Bool
Prelude.Eq, ReadPrec [GetDetector]
ReadPrec GetDetector
Int -> ReadS GetDetector
ReadS [GetDetector]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDetector]
$creadListPrec :: ReadPrec [GetDetector]
readPrec :: ReadPrec GetDetector
$creadPrec :: ReadPrec GetDetector
readList :: ReadS [GetDetector]
$creadList :: ReadS [GetDetector]
readsPrec :: Int -> ReadS GetDetector
$creadsPrec :: Int -> ReadS GetDetector
Prelude.Read, Int -> GetDetector -> ShowS
[GetDetector] -> ShowS
GetDetector -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDetector] -> ShowS
$cshowList :: [GetDetector] -> ShowS
show :: GetDetector -> String
$cshow :: GetDetector -> String
showsPrec :: Int -> GetDetector -> ShowS
$cshowsPrec :: Int -> GetDetector -> ShowS
Prelude.Show, forall x. Rep GetDetector x -> GetDetector
forall x. GetDetector -> Rep GetDetector x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDetector x -> GetDetector
$cfrom :: forall x. GetDetector -> Rep GetDetector x
Prelude.Generic)

-- |
-- Create a value of 'GetDetector' 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:
--
-- 'detectorId', 'getDetector_detectorId' - The unique ID of the detector that you want to get.
newGetDetector ::
  -- | 'detectorId'
  Prelude.Text ->
  GetDetector
newGetDetector :: Text -> GetDetector
newGetDetector Text
pDetectorId_ =
  GetDetector' {$sel:detectorId:GetDetector' :: Text
detectorId = Text
pDetectorId_}

-- | The unique ID of the detector that you want to get.
getDetector_detectorId :: Lens.Lens' GetDetector Prelude.Text
getDetector_detectorId :: Lens' GetDetector Text
getDetector_detectorId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDetector' {Text
detectorId :: Text
$sel:detectorId:GetDetector' :: GetDetector -> Text
detectorId} -> Text
detectorId) (\s :: GetDetector
s@GetDetector' {} Text
a -> GetDetector
s {$sel:detectorId:GetDetector' :: Text
detectorId = Text
a} :: GetDetector)

instance Core.AWSRequest GetDetector where
  type AWSResponse GetDetector = GetDetectorResponse
  request :: (Service -> Service) -> GetDetector -> Request GetDetector
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetDetector
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDetector)))
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
-> Maybe DataSourceConfigurationsResult
-> Maybe FindingPublishingFrequency
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Int
-> Text
-> DetectorStatus
-> GetDetectorResponse
GetDetectorResponse'
            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
"createdAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"dataSources")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"findingPublishingFrequency")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"updatedAt")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"serviceRole")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"status")
      )

instance Prelude.Hashable GetDetector where
  hashWithSalt :: Int -> GetDetector -> Int
hashWithSalt Int
_salt GetDetector' {Text
detectorId :: Text
$sel:detectorId:GetDetector' :: GetDetector -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
detectorId

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

instance Data.ToHeaders GetDetector where
  toHeaders :: GetDetector -> 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.ToPath GetDetector where
  toPath :: GetDetector -> ByteString
toPath GetDetector' {Text
detectorId :: Text
$sel:detectorId:GetDetector' :: GetDetector -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/detector/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
detectorId]

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

-- | /See:/ 'newGetDetectorResponse' smart constructor.
data GetDetectorResponse = GetDetectorResponse'
  { -- | The timestamp of when the detector was created.
    GetDetectorResponse -> Maybe Text
createdAt :: Prelude.Maybe Prelude.Text,
    -- | Describes which data sources are enabled for the detector.
    GetDetectorResponse -> Maybe DataSourceConfigurationsResult
dataSources :: Prelude.Maybe DataSourceConfigurationsResult,
    -- | The publishing frequency of the finding.
    GetDetectorResponse -> Maybe FindingPublishingFrequency
findingPublishingFrequency :: Prelude.Maybe FindingPublishingFrequency,
    -- | The tags of the detector resource.
    GetDetectorResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The last-updated timestamp for the detector.
    GetDetectorResponse -> Maybe Text
updatedAt :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetDetectorResponse -> Int
httpStatus :: Prelude.Int,
    -- | The GuardDuty service role.
    GetDetectorResponse -> Text
serviceRole :: Prelude.Text,
    -- | The detector status.
    GetDetectorResponse -> DetectorStatus
status :: DetectorStatus
  }
  deriving (GetDetectorResponse -> GetDetectorResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDetectorResponse -> GetDetectorResponse -> Bool
$c/= :: GetDetectorResponse -> GetDetectorResponse -> Bool
== :: GetDetectorResponse -> GetDetectorResponse -> Bool
$c== :: GetDetectorResponse -> GetDetectorResponse -> Bool
Prelude.Eq, ReadPrec [GetDetectorResponse]
ReadPrec GetDetectorResponse
Int -> ReadS GetDetectorResponse
ReadS [GetDetectorResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDetectorResponse]
$creadListPrec :: ReadPrec [GetDetectorResponse]
readPrec :: ReadPrec GetDetectorResponse
$creadPrec :: ReadPrec GetDetectorResponse
readList :: ReadS [GetDetectorResponse]
$creadList :: ReadS [GetDetectorResponse]
readsPrec :: Int -> ReadS GetDetectorResponse
$creadsPrec :: Int -> ReadS GetDetectorResponse
Prelude.Read, Int -> GetDetectorResponse -> ShowS
[GetDetectorResponse] -> ShowS
GetDetectorResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDetectorResponse] -> ShowS
$cshowList :: [GetDetectorResponse] -> ShowS
show :: GetDetectorResponse -> String
$cshow :: GetDetectorResponse -> String
showsPrec :: Int -> GetDetectorResponse -> ShowS
$cshowsPrec :: Int -> GetDetectorResponse -> ShowS
Prelude.Show, forall x. Rep GetDetectorResponse x -> GetDetectorResponse
forall x. GetDetectorResponse -> Rep GetDetectorResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDetectorResponse x -> GetDetectorResponse
$cfrom :: forall x. GetDetectorResponse -> Rep GetDetectorResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDetectorResponse' 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:
--
-- 'createdAt', 'getDetectorResponse_createdAt' - The timestamp of when the detector was created.
--
-- 'dataSources', 'getDetectorResponse_dataSources' - Describes which data sources are enabled for the detector.
--
-- 'findingPublishingFrequency', 'getDetectorResponse_findingPublishingFrequency' - The publishing frequency of the finding.
--
-- 'tags', 'getDetectorResponse_tags' - The tags of the detector resource.
--
-- 'updatedAt', 'getDetectorResponse_updatedAt' - The last-updated timestamp for the detector.
--
-- 'httpStatus', 'getDetectorResponse_httpStatus' - The response's http status code.
--
-- 'serviceRole', 'getDetectorResponse_serviceRole' - The GuardDuty service role.
--
-- 'status', 'getDetectorResponse_status' - The detector status.
newGetDetectorResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'serviceRole'
  Prelude.Text ->
  -- | 'status'
  DetectorStatus ->
  GetDetectorResponse
newGetDetectorResponse :: Int -> Text -> DetectorStatus -> GetDetectorResponse
newGetDetectorResponse
  Int
pHttpStatus_
  Text
pServiceRole_
  DetectorStatus
pStatus_ =
    GetDetectorResponse'
      { $sel:createdAt:GetDetectorResponse' :: Maybe Text
createdAt = forall a. Maybe a
Prelude.Nothing,
        $sel:dataSources:GetDetectorResponse' :: Maybe DataSourceConfigurationsResult
dataSources = forall a. Maybe a
Prelude.Nothing,
        $sel:findingPublishingFrequency:GetDetectorResponse' :: Maybe FindingPublishingFrequency
findingPublishingFrequency = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:GetDetectorResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:updatedAt:GetDetectorResponse' :: Maybe Text
updatedAt = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetDetectorResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:serviceRole:GetDetectorResponse' :: Text
serviceRole = Text
pServiceRole_,
        $sel:status:GetDetectorResponse' :: DetectorStatus
status = DetectorStatus
pStatus_
      }

-- | The timestamp of when the detector was created.
getDetectorResponse_createdAt :: Lens.Lens' GetDetectorResponse (Prelude.Maybe Prelude.Text)
getDetectorResponse_createdAt :: Lens' GetDetectorResponse (Maybe Text)
getDetectorResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDetectorResponse' {Maybe Text
createdAt :: Maybe Text
$sel:createdAt:GetDetectorResponse' :: GetDetectorResponse -> Maybe Text
createdAt} -> Maybe Text
createdAt) (\s :: GetDetectorResponse
s@GetDetectorResponse' {} Maybe Text
a -> GetDetectorResponse
s {$sel:createdAt:GetDetectorResponse' :: Maybe Text
createdAt = Maybe Text
a} :: GetDetectorResponse)

-- | Describes which data sources are enabled for the detector.
getDetectorResponse_dataSources :: Lens.Lens' GetDetectorResponse (Prelude.Maybe DataSourceConfigurationsResult)
getDetectorResponse_dataSources :: Lens' GetDetectorResponse (Maybe DataSourceConfigurationsResult)
getDetectorResponse_dataSources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDetectorResponse' {Maybe DataSourceConfigurationsResult
dataSources :: Maybe DataSourceConfigurationsResult
$sel:dataSources:GetDetectorResponse' :: GetDetectorResponse -> Maybe DataSourceConfigurationsResult
dataSources} -> Maybe DataSourceConfigurationsResult
dataSources) (\s :: GetDetectorResponse
s@GetDetectorResponse' {} Maybe DataSourceConfigurationsResult
a -> GetDetectorResponse
s {$sel:dataSources:GetDetectorResponse' :: Maybe DataSourceConfigurationsResult
dataSources = Maybe DataSourceConfigurationsResult
a} :: GetDetectorResponse)

-- | The publishing frequency of the finding.
getDetectorResponse_findingPublishingFrequency :: Lens.Lens' GetDetectorResponse (Prelude.Maybe FindingPublishingFrequency)
getDetectorResponse_findingPublishingFrequency :: Lens' GetDetectorResponse (Maybe FindingPublishingFrequency)
getDetectorResponse_findingPublishingFrequency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDetectorResponse' {Maybe FindingPublishingFrequency
findingPublishingFrequency :: Maybe FindingPublishingFrequency
$sel:findingPublishingFrequency:GetDetectorResponse' :: GetDetectorResponse -> Maybe FindingPublishingFrequency
findingPublishingFrequency} -> Maybe FindingPublishingFrequency
findingPublishingFrequency) (\s :: GetDetectorResponse
s@GetDetectorResponse' {} Maybe FindingPublishingFrequency
a -> GetDetectorResponse
s {$sel:findingPublishingFrequency:GetDetectorResponse' :: Maybe FindingPublishingFrequency
findingPublishingFrequency = Maybe FindingPublishingFrequency
a} :: GetDetectorResponse)

-- | The tags of the detector resource.
getDetectorResponse_tags :: Lens.Lens' GetDetectorResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getDetectorResponse_tags :: Lens' GetDetectorResponse (Maybe (HashMap Text Text))
getDetectorResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDetectorResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetDetectorResponse' :: GetDetectorResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetDetectorResponse
s@GetDetectorResponse' {} Maybe (HashMap Text Text)
a -> GetDetectorResponse
s {$sel:tags:GetDetectorResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetDetectorResponse) 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 last-updated timestamp for the detector.
getDetectorResponse_updatedAt :: Lens.Lens' GetDetectorResponse (Prelude.Maybe Prelude.Text)
getDetectorResponse_updatedAt :: Lens' GetDetectorResponse (Maybe Text)
getDetectorResponse_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDetectorResponse' {Maybe Text
updatedAt :: Maybe Text
$sel:updatedAt:GetDetectorResponse' :: GetDetectorResponse -> Maybe Text
updatedAt} -> Maybe Text
updatedAt) (\s :: GetDetectorResponse
s@GetDetectorResponse' {} Maybe Text
a -> GetDetectorResponse
s {$sel:updatedAt:GetDetectorResponse' :: Maybe Text
updatedAt = Maybe Text
a} :: GetDetectorResponse)

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

-- | The GuardDuty service role.
getDetectorResponse_serviceRole :: Lens.Lens' GetDetectorResponse Prelude.Text
getDetectorResponse_serviceRole :: Lens' GetDetectorResponse Text
getDetectorResponse_serviceRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDetectorResponse' {Text
serviceRole :: Text
$sel:serviceRole:GetDetectorResponse' :: GetDetectorResponse -> Text
serviceRole} -> Text
serviceRole) (\s :: GetDetectorResponse
s@GetDetectorResponse' {} Text
a -> GetDetectorResponse
s {$sel:serviceRole:GetDetectorResponse' :: Text
serviceRole = Text
a} :: GetDetectorResponse)

-- | The detector status.
getDetectorResponse_status :: Lens.Lens' GetDetectorResponse DetectorStatus
getDetectorResponse_status :: Lens' GetDetectorResponse DetectorStatus
getDetectorResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDetectorResponse' {DetectorStatus
status :: DetectorStatus
$sel:status:GetDetectorResponse' :: GetDetectorResponse -> DetectorStatus
status} -> DetectorStatus
status) (\s :: GetDetectorResponse
s@GetDetectorResponse' {} DetectorStatus
a -> GetDetectorResponse
s {$sel:status:GetDetectorResponse' :: DetectorStatus
status = DetectorStatus
a} :: GetDetectorResponse)

instance Prelude.NFData GetDetectorResponse where
  rnf :: GetDetectorResponse -> ()
rnf GetDetectorResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
Maybe FindingPublishingFrequency
Maybe DataSourceConfigurationsResult
Text
DetectorStatus
status :: DetectorStatus
serviceRole :: Text
httpStatus :: Int
updatedAt :: Maybe Text
tags :: Maybe (HashMap Text Text)
findingPublishingFrequency :: Maybe FindingPublishingFrequency
dataSources :: Maybe DataSourceConfigurationsResult
createdAt :: Maybe Text
$sel:status:GetDetectorResponse' :: GetDetectorResponse -> DetectorStatus
$sel:serviceRole:GetDetectorResponse' :: GetDetectorResponse -> Text
$sel:httpStatus:GetDetectorResponse' :: GetDetectorResponse -> Int
$sel:updatedAt:GetDetectorResponse' :: GetDetectorResponse -> Maybe Text
$sel:tags:GetDetectorResponse' :: GetDetectorResponse -> Maybe (HashMap Text Text)
$sel:findingPublishingFrequency:GetDetectorResponse' :: GetDetectorResponse -> Maybe FindingPublishingFrequency
$sel:dataSources:GetDetectorResponse' :: GetDetectorResponse -> Maybe DataSourceConfigurationsResult
$sel:createdAt:GetDetectorResponse' :: GetDetectorResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceConfigurationsResult
dataSources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FindingPublishingFrequency
findingPublishingFrequency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
updatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serviceRole
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DetectorStatus
status