{-# 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.GetIPSet
-- 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 the IPSet specified by the @ipSetId@.
module Amazonka.GuardDuty.GetIPSet
  ( -- * Creating a Request
    GetIPSet (..),
    newGetIPSet,

    -- * Request Lenses
    getIPSet_detectorId,
    getIPSet_ipSetId,

    -- * Destructuring the Response
    GetIPSetResponse (..),
    newGetIPSetResponse,

    -- * Response Lenses
    getIPSetResponse_tags,
    getIPSetResponse_httpStatus,
    getIPSetResponse_name,
    getIPSetResponse_format,
    getIPSetResponse_location,
    getIPSetResponse_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:/ 'newGetIPSet' smart constructor.
data GetIPSet = GetIPSet'
  { -- | The unique ID of the detector that the IPSet is associated with.
    GetIPSet -> Text
detectorId :: Prelude.Text,
    -- | The unique ID of the IPSet to retrieve.
    GetIPSet -> Text
ipSetId :: Prelude.Text
  }
  deriving (GetIPSet -> GetIPSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIPSet -> GetIPSet -> Bool
$c/= :: GetIPSet -> GetIPSet -> Bool
== :: GetIPSet -> GetIPSet -> Bool
$c== :: GetIPSet -> GetIPSet -> Bool
Prelude.Eq, ReadPrec [GetIPSet]
ReadPrec GetIPSet
Int -> ReadS GetIPSet
ReadS [GetIPSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIPSet]
$creadListPrec :: ReadPrec [GetIPSet]
readPrec :: ReadPrec GetIPSet
$creadPrec :: ReadPrec GetIPSet
readList :: ReadS [GetIPSet]
$creadList :: ReadS [GetIPSet]
readsPrec :: Int -> ReadS GetIPSet
$creadsPrec :: Int -> ReadS GetIPSet
Prelude.Read, Int -> GetIPSet -> ShowS
[GetIPSet] -> ShowS
GetIPSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIPSet] -> ShowS
$cshowList :: [GetIPSet] -> ShowS
show :: GetIPSet -> String
$cshow :: GetIPSet -> String
showsPrec :: Int -> GetIPSet -> ShowS
$cshowsPrec :: Int -> GetIPSet -> ShowS
Prelude.Show, forall x. Rep GetIPSet x -> GetIPSet
forall x. GetIPSet -> Rep GetIPSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetIPSet x -> GetIPSet
$cfrom :: forall x. GetIPSet -> Rep GetIPSet x
Prelude.Generic)

-- |
-- Create a value of 'GetIPSet' 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', 'getIPSet_detectorId' - The unique ID of the detector that the IPSet is associated with.
--
-- 'ipSetId', 'getIPSet_ipSetId' - The unique ID of the IPSet to retrieve.
newGetIPSet ::
  -- | 'detectorId'
  Prelude.Text ->
  -- | 'ipSetId'
  Prelude.Text ->
  GetIPSet
newGetIPSet :: Text -> Text -> GetIPSet
newGetIPSet Text
pDetectorId_ Text
pIpSetId_ =
  GetIPSet'
    { $sel:detectorId:GetIPSet' :: Text
detectorId = Text
pDetectorId_,
      $sel:ipSetId:GetIPSet' :: Text
ipSetId = Text
pIpSetId_
    }

-- | The unique ID of the detector that the IPSet is associated with.
getIPSet_detectorId :: Lens.Lens' GetIPSet Prelude.Text
getIPSet_detectorId :: Lens' GetIPSet Text
getIPSet_detectorId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIPSet' {Text
detectorId :: Text
$sel:detectorId:GetIPSet' :: GetIPSet -> Text
detectorId} -> Text
detectorId) (\s :: GetIPSet
s@GetIPSet' {} Text
a -> GetIPSet
s {$sel:detectorId:GetIPSet' :: Text
detectorId = Text
a} :: GetIPSet)

-- | The unique ID of the IPSet to retrieve.
getIPSet_ipSetId :: Lens.Lens' GetIPSet Prelude.Text
getIPSet_ipSetId :: Lens' GetIPSet Text
getIPSet_ipSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIPSet' {Text
ipSetId :: Text
$sel:ipSetId:GetIPSet' :: GetIPSet -> Text
ipSetId} -> Text
ipSetId) (\s :: GetIPSet
s@GetIPSet' {} Text
a -> GetIPSet
s {$sel:ipSetId:GetIPSet' :: Text
ipSetId = Text
a} :: GetIPSet)

instance Core.AWSRequest GetIPSet where
  type AWSResponse GetIPSet = GetIPSetResponse
  request :: (Service -> Service) -> GetIPSet -> Request GetIPSet
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 GetIPSet
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetIPSet)))
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 (HashMap Text Text)
-> Int
-> Text
-> IpSetFormat
-> Text
-> IpSetStatus
-> GetIPSetResponse
GetIPSetResponse'
            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
"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.<*> (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
"name")
            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
"format")
            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
"location")
            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 GetIPSet where
  hashWithSalt :: Int -> GetIPSet -> Int
hashWithSalt Int
_salt GetIPSet' {Text
ipSetId :: Text
detectorId :: Text
$sel:ipSetId:GetIPSet' :: GetIPSet -> Text
$sel:detectorId:GetIPSet' :: GetIPSet -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
detectorId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ipSetId

instance Prelude.NFData GetIPSet where
  rnf :: GetIPSet -> ()
rnf GetIPSet' {Text
ipSetId :: Text
detectorId :: Text
$sel:ipSetId:GetIPSet' :: GetIPSet -> Text
$sel:detectorId:GetIPSet' :: GetIPSet -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
detectorId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ipSetId

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

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

-- | /See:/ 'newGetIPSetResponse' smart constructor.
data GetIPSetResponse = GetIPSetResponse'
  { -- | The tags of the IPSet resource.
    GetIPSetResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    GetIPSetResponse -> Int
httpStatus :: Prelude.Int,
    -- | The user-friendly name for the IPSet.
    GetIPSetResponse -> Text
name :: Prelude.Text,
    -- | The format of the file that contains the IPSet.
    GetIPSetResponse -> IpSetFormat
format :: IpSetFormat,
    -- | The URI of the file that contains the IPSet.
    GetIPSetResponse -> Text
location :: Prelude.Text,
    -- | The status of IPSet file that was uploaded.
    GetIPSetResponse -> IpSetStatus
status :: IpSetStatus
  }
  deriving (GetIPSetResponse -> GetIPSetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIPSetResponse -> GetIPSetResponse -> Bool
$c/= :: GetIPSetResponse -> GetIPSetResponse -> Bool
== :: GetIPSetResponse -> GetIPSetResponse -> Bool
$c== :: GetIPSetResponse -> GetIPSetResponse -> Bool
Prelude.Eq, ReadPrec [GetIPSetResponse]
ReadPrec GetIPSetResponse
Int -> ReadS GetIPSetResponse
ReadS [GetIPSetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIPSetResponse]
$creadListPrec :: ReadPrec [GetIPSetResponse]
readPrec :: ReadPrec GetIPSetResponse
$creadPrec :: ReadPrec GetIPSetResponse
readList :: ReadS [GetIPSetResponse]
$creadList :: ReadS [GetIPSetResponse]
readsPrec :: Int -> ReadS GetIPSetResponse
$creadsPrec :: Int -> ReadS GetIPSetResponse
Prelude.Read, Int -> GetIPSetResponse -> ShowS
[GetIPSetResponse] -> ShowS
GetIPSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIPSetResponse] -> ShowS
$cshowList :: [GetIPSetResponse] -> ShowS
show :: GetIPSetResponse -> String
$cshow :: GetIPSetResponse -> String
showsPrec :: Int -> GetIPSetResponse -> ShowS
$cshowsPrec :: Int -> GetIPSetResponse -> ShowS
Prelude.Show, forall x. Rep GetIPSetResponse x -> GetIPSetResponse
forall x. GetIPSetResponse -> Rep GetIPSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetIPSetResponse x -> GetIPSetResponse
$cfrom :: forall x. GetIPSetResponse -> Rep GetIPSetResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetIPSetResponse' 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:
--
-- 'tags', 'getIPSetResponse_tags' - The tags of the IPSet resource.
--
-- 'httpStatus', 'getIPSetResponse_httpStatus' - The response's http status code.
--
-- 'name', 'getIPSetResponse_name' - The user-friendly name for the IPSet.
--
-- 'format', 'getIPSetResponse_format' - The format of the file that contains the IPSet.
--
-- 'location', 'getIPSetResponse_location' - The URI of the file that contains the IPSet.
--
-- 'status', 'getIPSetResponse_status' - The status of IPSet file that was uploaded.
newGetIPSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'name'
  Prelude.Text ->
  -- | 'format'
  IpSetFormat ->
  -- | 'location'
  Prelude.Text ->
  -- | 'status'
  IpSetStatus ->
  GetIPSetResponse
newGetIPSetResponse :: Int
-> Text -> IpSetFormat -> Text -> IpSetStatus -> GetIPSetResponse
newGetIPSetResponse
  Int
pHttpStatus_
  Text
pName_
  IpSetFormat
pFormat_
  Text
pLocation_
  IpSetStatus
pStatus_ =
    GetIPSetResponse'
      { $sel:tags:GetIPSetResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetIPSetResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:name:GetIPSetResponse' :: Text
name = Text
pName_,
        $sel:format:GetIPSetResponse' :: IpSetFormat
format = IpSetFormat
pFormat_,
        $sel:location:GetIPSetResponse' :: Text
location = Text
pLocation_,
        $sel:status:GetIPSetResponse' :: IpSetStatus
status = IpSetStatus
pStatus_
      }

-- | The tags of the IPSet resource.
getIPSetResponse_tags :: Lens.Lens' GetIPSetResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getIPSetResponse_tags :: Lens' GetIPSetResponse (Maybe (HashMap Text Text))
getIPSetResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIPSetResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetIPSetResponse' :: GetIPSetResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetIPSetResponse
s@GetIPSetResponse' {} Maybe (HashMap Text Text)
a -> GetIPSetResponse
s {$sel:tags:GetIPSetResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetIPSetResponse) 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 response's http status code.
getIPSetResponse_httpStatus :: Lens.Lens' GetIPSetResponse Prelude.Int
getIPSetResponse_httpStatus :: Lens' GetIPSetResponse Int
getIPSetResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIPSetResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetIPSetResponse' :: GetIPSetResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetIPSetResponse
s@GetIPSetResponse' {} Int
a -> GetIPSetResponse
s {$sel:httpStatus:GetIPSetResponse' :: Int
httpStatus = Int
a} :: GetIPSetResponse)

-- | The user-friendly name for the IPSet.
getIPSetResponse_name :: Lens.Lens' GetIPSetResponse Prelude.Text
getIPSetResponse_name :: Lens' GetIPSetResponse Text
getIPSetResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIPSetResponse' {Text
name :: Text
$sel:name:GetIPSetResponse' :: GetIPSetResponse -> Text
name} -> Text
name) (\s :: GetIPSetResponse
s@GetIPSetResponse' {} Text
a -> GetIPSetResponse
s {$sel:name:GetIPSetResponse' :: Text
name = Text
a} :: GetIPSetResponse)

-- | The format of the file that contains the IPSet.
getIPSetResponse_format :: Lens.Lens' GetIPSetResponse IpSetFormat
getIPSetResponse_format :: Lens' GetIPSetResponse IpSetFormat
getIPSetResponse_format = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIPSetResponse' {IpSetFormat
format :: IpSetFormat
$sel:format:GetIPSetResponse' :: GetIPSetResponse -> IpSetFormat
format} -> IpSetFormat
format) (\s :: GetIPSetResponse
s@GetIPSetResponse' {} IpSetFormat
a -> GetIPSetResponse
s {$sel:format:GetIPSetResponse' :: IpSetFormat
format = IpSetFormat
a} :: GetIPSetResponse)

-- | The URI of the file that contains the IPSet.
getIPSetResponse_location :: Lens.Lens' GetIPSetResponse Prelude.Text
getIPSetResponse_location :: Lens' GetIPSetResponse Text
getIPSetResponse_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIPSetResponse' {Text
location :: Text
$sel:location:GetIPSetResponse' :: GetIPSetResponse -> Text
location} -> Text
location) (\s :: GetIPSetResponse
s@GetIPSetResponse' {} Text
a -> GetIPSetResponse
s {$sel:location:GetIPSetResponse' :: Text
location = Text
a} :: GetIPSetResponse)

-- | The status of IPSet file that was uploaded.
getIPSetResponse_status :: Lens.Lens' GetIPSetResponse IpSetStatus
getIPSetResponse_status :: Lens' GetIPSetResponse IpSetStatus
getIPSetResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIPSetResponse' {IpSetStatus
status :: IpSetStatus
$sel:status:GetIPSetResponse' :: GetIPSetResponse -> IpSetStatus
status} -> IpSetStatus
status) (\s :: GetIPSetResponse
s@GetIPSetResponse' {} IpSetStatus
a -> GetIPSetResponse
s {$sel:status:GetIPSetResponse' :: IpSetStatus
status = IpSetStatus
a} :: GetIPSetResponse)

instance Prelude.NFData GetIPSetResponse where
  rnf :: GetIPSetResponse -> ()
rnf GetIPSetResponse' {Int
Maybe (HashMap Text Text)
Text
IpSetFormat
IpSetStatus
status :: IpSetStatus
location :: Text
format :: IpSetFormat
name :: Text
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
$sel:status:GetIPSetResponse' :: GetIPSetResponse -> IpSetStatus
$sel:location:GetIPSetResponse' :: GetIPSetResponse -> Text
$sel:format:GetIPSetResponse' :: GetIPSetResponse -> IpSetFormat
$sel:name:GetIPSetResponse' :: GetIPSetResponse -> Text
$sel:httpStatus:GetIPSetResponse' :: GetIPSetResponse -> Int
$sel:tags:GetIPSetResponse' :: GetIPSetResponse -> Maybe (HashMap Text Text)
..} =
    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 Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IpSetFormat
format
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IpSetStatus
status