{-# 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.Route53Resolver.CreateFirewallDomainList
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates an empty firewall domain list for use in DNS Firewall rules. You
-- can populate the domains for the new list with a file, using
-- ImportFirewallDomains, or with domain strings, using
-- UpdateFirewallDomains.
module Amazonka.Route53Resolver.CreateFirewallDomainList
  ( -- * Creating a Request
    CreateFirewallDomainList (..),
    newCreateFirewallDomainList,

    -- * Request Lenses
    createFirewallDomainList_tags,
    createFirewallDomainList_creatorRequestId,
    createFirewallDomainList_name,

    -- * Destructuring the Response
    CreateFirewallDomainListResponse (..),
    newCreateFirewallDomainListResponse,

    -- * Response Lenses
    createFirewallDomainListResponse_firewallDomainList,
    createFirewallDomainListResponse_httpStatus,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Route53Resolver.Types

-- | /See:/ 'newCreateFirewallDomainList' smart constructor.
data CreateFirewallDomainList = CreateFirewallDomainList'
  { -- | A list of the tag keys and values that you want to associate with the
    -- domain list.
    CreateFirewallDomainList -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A unique string that identifies the request and that allows you to retry
    -- failed requests without the risk of running the operation twice.
    -- @CreatorRequestId@ can be any unique string, for example, a date\/time
    -- stamp.
    CreateFirewallDomainList -> Text
creatorRequestId :: Prelude.Text,
    -- | A name that lets you identify the domain list to manage and use it.
    CreateFirewallDomainList -> Text
name :: Prelude.Text
  }
  deriving (CreateFirewallDomainList -> CreateFirewallDomainList -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFirewallDomainList -> CreateFirewallDomainList -> Bool
$c/= :: CreateFirewallDomainList -> CreateFirewallDomainList -> Bool
== :: CreateFirewallDomainList -> CreateFirewallDomainList -> Bool
$c== :: CreateFirewallDomainList -> CreateFirewallDomainList -> Bool
Prelude.Eq, ReadPrec [CreateFirewallDomainList]
ReadPrec CreateFirewallDomainList
Int -> ReadS CreateFirewallDomainList
ReadS [CreateFirewallDomainList]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFirewallDomainList]
$creadListPrec :: ReadPrec [CreateFirewallDomainList]
readPrec :: ReadPrec CreateFirewallDomainList
$creadPrec :: ReadPrec CreateFirewallDomainList
readList :: ReadS [CreateFirewallDomainList]
$creadList :: ReadS [CreateFirewallDomainList]
readsPrec :: Int -> ReadS CreateFirewallDomainList
$creadsPrec :: Int -> ReadS CreateFirewallDomainList
Prelude.Read, Int -> CreateFirewallDomainList -> ShowS
[CreateFirewallDomainList] -> ShowS
CreateFirewallDomainList -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFirewallDomainList] -> ShowS
$cshowList :: [CreateFirewallDomainList] -> ShowS
show :: CreateFirewallDomainList -> String
$cshow :: CreateFirewallDomainList -> String
showsPrec :: Int -> CreateFirewallDomainList -> ShowS
$cshowsPrec :: Int -> CreateFirewallDomainList -> ShowS
Prelude.Show, forall x.
Rep CreateFirewallDomainList x -> CreateFirewallDomainList
forall x.
CreateFirewallDomainList -> Rep CreateFirewallDomainList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateFirewallDomainList x -> CreateFirewallDomainList
$cfrom :: forall x.
CreateFirewallDomainList -> Rep CreateFirewallDomainList x
Prelude.Generic)

-- |
-- Create a value of 'CreateFirewallDomainList' 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', 'createFirewallDomainList_tags' - A list of the tag keys and values that you want to associate with the
-- domain list.
--
-- 'creatorRequestId', 'createFirewallDomainList_creatorRequestId' - A unique string that identifies the request and that allows you to retry
-- failed requests without the risk of running the operation twice.
-- @CreatorRequestId@ can be any unique string, for example, a date\/time
-- stamp.
--
-- 'name', 'createFirewallDomainList_name' - A name that lets you identify the domain list to manage and use it.
newCreateFirewallDomainList ::
  -- | 'creatorRequestId'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  CreateFirewallDomainList
newCreateFirewallDomainList :: Text -> Text -> CreateFirewallDomainList
newCreateFirewallDomainList Text
pCreatorRequestId_ Text
pName_ =
  CreateFirewallDomainList'
    { $sel:tags:CreateFirewallDomainList' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:creatorRequestId:CreateFirewallDomainList' :: Text
creatorRequestId = Text
pCreatorRequestId_,
      $sel:name:CreateFirewallDomainList' :: Text
name = Text
pName_
    }

-- | A list of the tag keys and values that you want to associate with the
-- domain list.
createFirewallDomainList_tags :: Lens.Lens' CreateFirewallDomainList (Prelude.Maybe [Tag])
createFirewallDomainList_tags :: Lens' CreateFirewallDomainList (Maybe [Tag])
createFirewallDomainList_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFirewallDomainList' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateFirewallDomainList' :: CreateFirewallDomainList -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateFirewallDomainList
s@CreateFirewallDomainList' {} Maybe [Tag]
a -> CreateFirewallDomainList
s {$sel:tags:CreateFirewallDomainList' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateFirewallDomainList) 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

-- | A unique string that identifies the request and that allows you to retry
-- failed requests without the risk of running the operation twice.
-- @CreatorRequestId@ can be any unique string, for example, a date\/time
-- stamp.
createFirewallDomainList_creatorRequestId :: Lens.Lens' CreateFirewallDomainList Prelude.Text
createFirewallDomainList_creatorRequestId :: Lens' CreateFirewallDomainList Text
createFirewallDomainList_creatorRequestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFirewallDomainList' {Text
creatorRequestId :: Text
$sel:creatorRequestId:CreateFirewallDomainList' :: CreateFirewallDomainList -> Text
creatorRequestId} -> Text
creatorRequestId) (\s :: CreateFirewallDomainList
s@CreateFirewallDomainList' {} Text
a -> CreateFirewallDomainList
s {$sel:creatorRequestId:CreateFirewallDomainList' :: Text
creatorRequestId = Text
a} :: CreateFirewallDomainList)

-- | A name that lets you identify the domain list to manage and use it.
createFirewallDomainList_name :: Lens.Lens' CreateFirewallDomainList Prelude.Text
createFirewallDomainList_name :: Lens' CreateFirewallDomainList Text
createFirewallDomainList_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFirewallDomainList' {Text
name :: Text
$sel:name:CreateFirewallDomainList' :: CreateFirewallDomainList -> Text
name} -> Text
name) (\s :: CreateFirewallDomainList
s@CreateFirewallDomainList' {} Text
a -> CreateFirewallDomainList
s {$sel:name:CreateFirewallDomainList' :: Text
name = Text
a} :: CreateFirewallDomainList)

instance Core.AWSRequest CreateFirewallDomainList where
  type
    AWSResponse CreateFirewallDomainList =
      CreateFirewallDomainListResponse
  request :: (Service -> Service)
-> CreateFirewallDomainList -> Request CreateFirewallDomainList
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 CreateFirewallDomainList
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateFirewallDomainList)))
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 FirewallDomainList -> Int -> CreateFirewallDomainListResponse
CreateFirewallDomainListResponse'
            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
"FirewallDomainList")
            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 CreateFirewallDomainList where
  hashWithSalt :: Int -> CreateFirewallDomainList -> Int
hashWithSalt Int
_salt CreateFirewallDomainList' {Maybe [Tag]
Text
name :: Text
creatorRequestId :: Text
tags :: Maybe [Tag]
$sel:name:CreateFirewallDomainList' :: CreateFirewallDomainList -> Text
$sel:creatorRequestId:CreateFirewallDomainList' :: CreateFirewallDomainList -> Text
$sel:tags:CreateFirewallDomainList' :: CreateFirewallDomainList -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
creatorRequestId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateFirewallDomainList where
  rnf :: CreateFirewallDomainList -> ()
rnf CreateFirewallDomainList' {Maybe [Tag]
Text
name :: Text
creatorRequestId :: Text
tags :: Maybe [Tag]
$sel:name:CreateFirewallDomainList' :: CreateFirewallDomainList -> Text
$sel:creatorRequestId:CreateFirewallDomainList' :: CreateFirewallDomainList -> Text
$sel:tags:CreateFirewallDomainList' :: CreateFirewallDomainList -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
creatorRequestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders CreateFirewallDomainList where
  toHeaders :: CreateFirewallDomainList -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"Route53Resolver.CreateFirewallDomainList" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateFirewallDomainList where
  toJSON :: CreateFirewallDomainList -> Value
toJSON CreateFirewallDomainList' {Maybe [Tag]
Text
name :: Text
creatorRequestId :: Text
tags :: Maybe [Tag]
$sel:name:CreateFirewallDomainList' :: CreateFirewallDomainList -> Text
$sel:creatorRequestId:CreateFirewallDomainList' :: CreateFirewallDomainList -> Text
$sel:tags:CreateFirewallDomainList' :: CreateFirewallDomainList -> Maybe [Tag]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"CreatorRequestId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
creatorRequestId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

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

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

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

-- |
-- Create a value of 'CreateFirewallDomainListResponse' 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:
--
-- 'firewallDomainList', 'createFirewallDomainListResponse_firewallDomainList' - The domain list that you just created.
--
-- 'httpStatus', 'createFirewallDomainListResponse_httpStatus' - The response's http status code.
newCreateFirewallDomainListResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateFirewallDomainListResponse
newCreateFirewallDomainListResponse :: Int -> CreateFirewallDomainListResponse
newCreateFirewallDomainListResponse Int
pHttpStatus_ =
  CreateFirewallDomainListResponse'
    { $sel:firewallDomainList:CreateFirewallDomainListResponse' :: Maybe FirewallDomainList
firewallDomainList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateFirewallDomainListResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The domain list that you just created.
createFirewallDomainListResponse_firewallDomainList :: Lens.Lens' CreateFirewallDomainListResponse (Prelude.Maybe FirewallDomainList)
createFirewallDomainListResponse_firewallDomainList :: Lens' CreateFirewallDomainListResponse (Maybe FirewallDomainList)
createFirewallDomainListResponse_firewallDomainList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFirewallDomainListResponse' {Maybe FirewallDomainList
firewallDomainList :: Maybe FirewallDomainList
$sel:firewallDomainList:CreateFirewallDomainListResponse' :: CreateFirewallDomainListResponse -> Maybe FirewallDomainList
firewallDomainList} -> Maybe FirewallDomainList
firewallDomainList) (\s :: CreateFirewallDomainListResponse
s@CreateFirewallDomainListResponse' {} Maybe FirewallDomainList
a -> CreateFirewallDomainListResponse
s {$sel:firewallDomainList:CreateFirewallDomainListResponse' :: Maybe FirewallDomainList
firewallDomainList = Maybe FirewallDomainList
a} :: CreateFirewallDomainListResponse)

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

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