{-# 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.Config.PutStoredQuery
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Saves a new query or updates an existing saved query. The @QueryName@
-- must be unique for a single Amazon Web Services account and a single
-- Amazon Web Services Region. You can create upto 300 queries in a single
-- Amazon Web Services account and a single Amazon Web Services Region.
module Amazonka.Config.PutStoredQuery
  ( -- * Creating a Request
    PutStoredQuery (..),
    newPutStoredQuery,

    -- * Request Lenses
    putStoredQuery_tags,
    putStoredQuery_storedQuery,

    -- * Destructuring the Response
    PutStoredQueryResponse (..),
    newPutStoredQueryResponse,

    -- * Response Lenses
    putStoredQueryResponse_queryArn,
    putStoredQueryResponse_httpStatus,
  )
where

import Amazonka.Config.Types
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

-- | /See:/ 'newPutStoredQuery' smart constructor.
data PutStoredQuery = PutStoredQuery'
  { -- | A list of @Tags@ object.
    PutStoredQuery -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A list of @StoredQuery@ objects. The mandatory fields are @QueryName@
    -- and @Expression@.
    --
    -- When you are creating a query, you must provide a query name and an
    -- expression. When you are updating a query, you must provide a query name
    -- but updating the description is optional.
    PutStoredQuery -> StoredQuery
storedQuery :: StoredQuery
  }
  deriving (PutStoredQuery -> PutStoredQuery -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutStoredQuery -> PutStoredQuery -> Bool
$c/= :: PutStoredQuery -> PutStoredQuery -> Bool
== :: PutStoredQuery -> PutStoredQuery -> Bool
$c== :: PutStoredQuery -> PutStoredQuery -> Bool
Prelude.Eq, ReadPrec [PutStoredQuery]
ReadPrec PutStoredQuery
Int -> ReadS PutStoredQuery
ReadS [PutStoredQuery]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutStoredQuery]
$creadListPrec :: ReadPrec [PutStoredQuery]
readPrec :: ReadPrec PutStoredQuery
$creadPrec :: ReadPrec PutStoredQuery
readList :: ReadS [PutStoredQuery]
$creadList :: ReadS [PutStoredQuery]
readsPrec :: Int -> ReadS PutStoredQuery
$creadsPrec :: Int -> ReadS PutStoredQuery
Prelude.Read, Int -> PutStoredQuery -> ShowS
[PutStoredQuery] -> ShowS
PutStoredQuery -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutStoredQuery] -> ShowS
$cshowList :: [PutStoredQuery] -> ShowS
show :: PutStoredQuery -> String
$cshow :: PutStoredQuery -> String
showsPrec :: Int -> PutStoredQuery -> ShowS
$cshowsPrec :: Int -> PutStoredQuery -> ShowS
Prelude.Show, forall x. Rep PutStoredQuery x -> PutStoredQuery
forall x. PutStoredQuery -> Rep PutStoredQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutStoredQuery x -> PutStoredQuery
$cfrom :: forall x. PutStoredQuery -> Rep PutStoredQuery x
Prelude.Generic)

-- |
-- Create a value of 'PutStoredQuery' 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', 'putStoredQuery_tags' - A list of @Tags@ object.
--
-- 'storedQuery', 'putStoredQuery_storedQuery' - A list of @StoredQuery@ objects. The mandatory fields are @QueryName@
-- and @Expression@.
--
-- When you are creating a query, you must provide a query name and an
-- expression. When you are updating a query, you must provide a query name
-- but updating the description is optional.
newPutStoredQuery ::
  -- | 'storedQuery'
  StoredQuery ->
  PutStoredQuery
newPutStoredQuery :: StoredQuery -> PutStoredQuery
newPutStoredQuery StoredQuery
pStoredQuery_ =
  PutStoredQuery'
    { $sel:tags:PutStoredQuery' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:storedQuery:PutStoredQuery' :: StoredQuery
storedQuery = StoredQuery
pStoredQuery_
    }

-- | A list of @Tags@ object.
putStoredQuery_tags :: Lens.Lens' PutStoredQuery (Prelude.Maybe [Tag])
putStoredQuery_tags :: Lens' PutStoredQuery (Maybe [Tag])
putStoredQuery_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutStoredQuery' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:PutStoredQuery' :: PutStoredQuery -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: PutStoredQuery
s@PutStoredQuery' {} Maybe [Tag]
a -> PutStoredQuery
s {$sel:tags:PutStoredQuery' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: PutStoredQuery) 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 list of @StoredQuery@ objects. The mandatory fields are @QueryName@
-- and @Expression@.
--
-- When you are creating a query, you must provide a query name and an
-- expression. When you are updating a query, you must provide a query name
-- but updating the description is optional.
putStoredQuery_storedQuery :: Lens.Lens' PutStoredQuery StoredQuery
putStoredQuery_storedQuery :: Lens' PutStoredQuery StoredQuery
putStoredQuery_storedQuery = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutStoredQuery' {StoredQuery
storedQuery :: StoredQuery
$sel:storedQuery:PutStoredQuery' :: PutStoredQuery -> StoredQuery
storedQuery} -> StoredQuery
storedQuery) (\s :: PutStoredQuery
s@PutStoredQuery' {} StoredQuery
a -> PutStoredQuery
s {$sel:storedQuery:PutStoredQuery' :: StoredQuery
storedQuery = StoredQuery
a} :: PutStoredQuery)

instance Core.AWSRequest PutStoredQuery where
  type
    AWSResponse PutStoredQuery =
      PutStoredQueryResponse
  request :: (Service -> Service) -> PutStoredQuery -> Request PutStoredQuery
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 PutStoredQuery
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PutStoredQuery)))
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 -> PutStoredQueryResponse
PutStoredQueryResponse'
            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
"QueryArn")
            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 PutStoredQuery where
  hashWithSalt :: Int -> PutStoredQuery -> Int
hashWithSalt Int
_salt PutStoredQuery' {Maybe [Tag]
StoredQuery
storedQuery :: StoredQuery
tags :: Maybe [Tag]
$sel:storedQuery:PutStoredQuery' :: PutStoredQuery -> StoredQuery
$sel:tags:PutStoredQuery' :: PutStoredQuery -> 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` StoredQuery
storedQuery

instance Prelude.NFData PutStoredQuery where
  rnf :: PutStoredQuery -> ()
rnf PutStoredQuery' {Maybe [Tag]
StoredQuery
storedQuery :: StoredQuery
tags :: Maybe [Tag]
$sel:storedQuery:PutStoredQuery' :: PutStoredQuery -> StoredQuery
$sel:tags:PutStoredQuery' :: PutStoredQuery -> 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 StoredQuery
storedQuery

instance Data.ToHeaders PutStoredQuery where
  toHeaders :: PutStoredQuery -> 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
"StarlingDoveService.PutStoredQuery" ::
                          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 PutStoredQuery where
  toJSON :: PutStoredQuery -> Value
toJSON PutStoredQuery' {Maybe [Tag]
StoredQuery
storedQuery :: StoredQuery
tags :: Maybe [Tag]
$sel:storedQuery:PutStoredQuery' :: PutStoredQuery -> StoredQuery
$sel:tags:PutStoredQuery' :: PutStoredQuery -> 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
"StoredQuery" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= StoredQuery
storedQuery)
          ]
      )

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

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

-- | /See:/ 'newPutStoredQueryResponse' smart constructor.
data PutStoredQueryResponse = PutStoredQueryResponse'
  { -- | Amazon Resource Name (ARN) of the query. For example,
    -- arn:partition:service:region:account-id:resource-type\/resource-name\/resource-id.
    PutStoredQueryResponse -> Maybe Text
queryArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    PutStoredQueryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PutStoredQueryResponse -> PutStoredQueryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutStoredQueryResponse -> PutStoredQueryResponse -> Bool
$c/= :: PutStoredQueryResponse -> PutStoredQueryResponse -> Bool
== :: PutStoredQueryResponse -> PutStoredQueryResponse -> Bool
$c== :: PutStoredQueryResponse -> PutStoredQueryResponse -> Bool
Prelude.Eq, ReadPrec [PutStoredQueryResponse]
ReadPrec PutStoredQueryResponse
Int -> ReadS PutStoredQueryResponse
ReadS [PutStoredQueryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutStoredQueryResponse]
$creadListPrec :: ReadPrec [PutStoredQueryResponse]
readPrec :: ReadPrec PutStoredQueryResponse
$creadPrec :: ReadPrec PutStoredQueryResponse
readList :: ReadS [PutStoredQueryResponse]
$creadList :: ReadS [PutStoredQueryResponse]
readsPrec :: Int -> ReadS PutStoredQueryResponse
$creadsPrec :: Int -> ReadS PutStoredQueryResponse
Prelude.Read, Int -> PutStoredQueryResponse -> ShowS
[PutStoredQueryResponse] -> ShowS
PutStoredQueryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutStoredQueryResponse] -> ShowS
$cshowList :: [PutStoredQueryResponse] -> ShowS
show :: PutStoredQueryResponse -> String
$cshow :: PutStoredQueryResponse -> String
showsPrec :: Int -> PutStoredQueryResponse -> ShowS
$cshowsPrec :: Int -> PutStoredQueryResponse -> ShowS
Prelude.Show, forall x. Rep PutStoredQueryResponse x -> PutStoredQueryResponse
forall x. PutStoredQueryResponse -> Rep PutStoredQueryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutStoredQueryResponse x -> PutStoredQueryResponse
$cfrom :: forall x. PutStoredQueryResponse -> Rep PutStoredQueryResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutStoredQueryResponse' 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:
--
-- 'queryArn', 'putStoredQueryResponse_queryArn' - Amazon Resource Name (ARN) of the query. For example,
-- arn:partition:service:region:account-id:resource-type\/resource-name\/resource-id.
--
-- 'httpStatus', 'putStoredQueryResponse_httpStatus' - The response's http status code.
newPutStoredQueryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutStoredQueryResponse
newPutStoredQueryResponse :: Int -> PutStoredQueryResponse
newPutStoredQueryResponse Int
pHttpStatus_ =
  PutStoredQueryResponse'
    { $sel:queryArn:PutStoredQueryResponse' :: Maybe Text
queryArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutStoredQueryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Amazon Resource Name (ARN) of the query. For example,
-- arn:partition:service:region:account-id:resource-type\/resource-name\/resource-id.
putStoredQueryResponse_queryArn :: Lens.Lens' PutStoredQueryResponse (Prelude.Maybe Prelude.Text)
putStoredQueryResponse_queryArn :: Lens' PutStoredQueryResponse (Maybe Text)
putStoredQueryResponse_queryArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutStoredQueryResponse' {Maybe Text
queryArn :: Maybe Text
$sel:queryArn:PutStoredQueryResponse' :: PutStoredQueryResponse -> Maybe Text
queryArn} -> Maybe Text
queryArn) (\s :: PutStoredQueryResponse
s@PutStoredQueryResponse' {} Maybe Text
a -> PutStoredQueryResponse
s {$sel:queryArn:PutStoredQueryResponse' :: Maybe Text
queryArn = Maybe Text
a} :: PutStoredQueryResponse)

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

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