{-# 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.CodeBuild.InvalidateProjectCache
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Resets the cache for a project.
module Amazonka.CodeBuild.InvalidateProjectCache
  ( -- * Creating a Request
    InvalidateProjectCache (..),
    newInvalidateProjectCache,

    -- * Request Lenses
    invalidateProjectCache_projectName,

    -- * Destructuring the Response
    InvalidateProjectCacheResponse (..),
    newInvalidateProjectCacheResponse,

    -- * Response Lenses
    invalidateProjectCacheResponse_httpStatus,
  )
where

import Amazonka.CodeBuild.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:/ 'newInvalidateProjectCache' smart constructor.
data InvalidateProjectCache = InvalidateProjectCache'
  { -- | The name of the CodeBuild build project that the cache is reset for.
    InvalidateProjectCache -> Text
projectName :: Prelude.Text
  }
  deriving (InvalidateProjectCache -> InvalidateProjectCache -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InvalidateProjectCache -> InvalidateProjectCache -> Bool
$c/= :: InvalidateProjectCache -> InvalidateProjectCache -> Bool
== :: InvalidateProjectCache -> InvalidateProjectCache -> Bool
$c== :: InvalidateProjectCache -> InvalidateProjectCache -> Bool
Prelude.Eq, ReadPrec [InvalidateProjectCache]
ReadPrec InvalidateProjectCache
Int -> ReadS InvalidateProjectCache
ReadS [InvalidateProjectCache]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InvalidateProjectCache]
$creadListPrec :: ReadPrec [InvalidateProjectCache]
readPrec :: ReadPrec InvalidateProjectCache
$creadPrec :: ReadPrec InvalidateProjectCache
readList :: ReadS [InvalidateProjectCache]
$creadList :: ReadS [InvalidateProjectCache]
readsPrec :: Int -> ReadS InvalidateProjectCache
$creadsPrec :: Int -> ReadS InvalidateProjectCache
Prelude.Read, Int -> InvalidateProjectCache -> ShowS
[InvalidateProjectCache] -> ShowS
InvalidateProjectCache -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InvalidateProjectCache] -> ShowS
$cshowList :: [InvalidateProjectCache] -> ShowS
show :: InvalidateProjectCache -> String
$cshow :: InvalidateProjectCache -> String
showsPrec :: Int -> InvalidateProjectCache -> ShowS
$cshowsPrec :: Int -> InvalidateProjectCache -> ShowS
Prelude.Show, forall x. Rep InvalidateProjectCache x -> InvalidateProjectCache
forall x. InvalidateProjectCache -> Rep InvalidateProjectCache x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InvalidateProjectCache x -> InvalidateProjectCache
$cfrom :: forall x. InvalidateProjectCache -> Rep InvalidateProjectCache x
Prelude.Generic)

-- |
-- Create a value of 'InvalidateProjectCache' 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:
--
-- 'projectName', 'invalidateProjectCache_projectName' - The name of the CodeBuild build project that the cache is reset for.
newInvalidateProjectCache ::
  -- | 'projectName'
  Prelude.Text ->
  InvalidateProjectCache
newInvalidateProjectCache :: Text -> InvalidateProjectCache
newInvalidateProjectCache Text
pProjectName_ =
  InvalidateProjectCache'
    { $sel:projectName:InvalidateProjectCache' :: Text
projectName =
        Text
pProjectName_
    }

-- | The name of the CodeBuild build project that the cache is reset for.
invalidateProjectCache_projectName :: Lens.Lens' InvalidateProjectCache Prelude.Text
invalidateProjectCache_projectName :: Lens' InvalidateProjectCache Text
invalidateProjectCache_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InvalidateProjectCache' {Text
projectName :: Text
$sel:projectName:InvalidateProjectCache' :: InvalidateProjectCache -> Text
projectName} -> Text
projectName) (\s :: InvalidateProjectCache
s@InvalidateProjectCache' {} Text
a -> InvalidateProjectCache
s {$sel:projectName:InvalidateProjectCache' :: Text
projectName = Text
a} :: InvalidateProjectCache)

instance Core.AWSRequest InvalidateProjectCache where
  type
    AWSResponse InvalidateProjectCache =
      InvalidateProjectCacheResponse
  request :: (Service -> Service)
-> InvalidateProjectCache -> Request InvalidateProjectCache
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 InvalidateProjectCache
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse InvalidateProjectCache)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> InvalidateProjectCacheResponse
InvalidateProjectCacheResponse'
            forall (f :: * -> *) a b. Functor 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 InvalidateProjectCache where
  hashWithSalt :: Int -> InvalidateProjectCache -> Int
hashWithSalt Int
_salt InvalidateProjectCache' {Text
projectName :: Text
$sel:projectName:InvalidateProjectCache' :: InvalidateProjectCache -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectName

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

instance Data.ToHeaders InvalidateProjectCache where
  toHeaders :: InvalidateProjectCache -> 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
"CodeBuild_20161006.InvalidateProjectCache" ::
                          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 InvalidateProjectCache where
  toJSON :: InvalidateProjectCache -> Value
toJSON InvalidateProjectCache' {Text
projectName :: Text
$sel:projectName:InvalidateProjectCache' :: InvalidateProjectCache -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"projectName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
projectName)]
      )

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

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

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

-- |
-- Create a value of 'InvalidateProjectCacheResponse' 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:
--
-- 'httpStatus', 'invalidateProjectCacheResponse_httpStatus' - The response's http status code.
newInvalidateProjectCacheResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  InvalidateProjectCacheResponse
newInvalidateProjectCacheResponse :: Int -> InvalidateProjectCacheResponse
newInvalidateProjectCacheResponse Int
pHttpStatus_ =
  InvalidateProjectCacheResponse'
    { $sel:httpStatus:InvalidateProjectCacheResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    InvalidateProjectCacheResponse
  where
  rnf :: InvalidateProjectCacheResponse -> ()
rnf InvalidateProjectCacheResponse' {Int
httpStatus :: Int
$sel:httpStatus:InvalidateProjectCacheResponse' :: InvalidateProjectCacheResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus