{-# 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.Synthetics.StartCanary
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Use this operation to run a canary that has already been created. The
-- frequency of the canary runs is determined by the value of the canary\'s
-- @Schedule@. To see a canary\'s schedule, use
-- <https://docs.aws.amazon.com/AmazonSynthetics/latest/APIReference/API_GetCanary.html GetCanary>.
module Amazonka.Synthetics.StartCanary
  ( -- * Creating a Request
    StartCanary (..),
    newStartCanary,

    -- * Request Lenses
    startCanary_name,

    -- * Destructuring the Response
    StartCanaryResponse (..),
    newStartCanaryResponse,

    -- * Response Lenses
    startCanaryResponse_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.Synthetics.Types

-- | /See:/ 'newStartCanary' smart constructor.
data StartCanary = StartCanary'
  { -- | The name of the canary that you want to run. To find canary names, use
    -- <https://docs.aws.amazon.com/AmazonSynthetics/latest/APIReference/API_DescribeCanaries.html DescribeCanaries>.
    StartCanary -> Text
name :: Prelude.Text
  }
  deriving (StartCanary -> StartCanary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartCanary -> StartCanary -> Bool
$c/= :: StartCanary -> StartCanary -> Bool
== :: StartCanary -> StartCanary -> Bool
$c== :: StartCanary -> StartCanary -> Bool
Prelude.Eq, ReadPrec [StartCanary]
ReadPrec StartCanary
Int -> ReadS StartCanary
ReadS [StartCanary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartCanary]
$creadListPrec :: ReadPrec [StartCanary]
readPrec :: ReadPrec StartCanary
$creadPrec :: ReadPrec StartCanary
readList :: ReadS [StartCanary]
$creadList :: ReadS [StartCanary]
readsPrec :: Int -> ReadS StartCanary
$creadsPrec :: Int -> ReadS StartCanary
Prelude.Read, Int -> StartCanary -> ShowS
[StartCanary] -> ShowS
StartCanary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartCanary] -> ShowS
$cshowList :: [StartCanary] -> ShowS
show :: StartCanary -> String
$cshow :: StartCanary -> String
showsPrec :: Int -> StartCanary -> ShowS
$cshowsPrec :: Int -> StartCanary -> ShowS
Prelude.Show, forall x. Rep StartCanary x -> StartCanary
forall x. StartCanary -> Rep StartCanary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartCanary x -> StartCanary
$cfrom :: forall x. StartCanary -> Rep StartCanary x
Prelude.Generic)

-- |
-- Create a value of 'StartCanary' 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:
--
-- 'name', 'startCanary_name' - The name of the canary that you want to run. To find canary names, use
-- <https://docs.aws.amazon.com/AmazonSynthetics/latest/APIReference/API_DescribeCanaries.html DescribeCanaries>.
newStartCanary ::
  -- | 'name'
  Prelude.Text ->
  StartCanary
newStartCanary :: Text -> StartCanary
newStartCanary Text
pName_ = StartCanary' {$sel:name:StartCanary' :: Text
name = Text
pName_}

-- | The name of the canary that you want to run. To find canary names, use
-- <https://docs.aws.amazon.com/AmazonSynthetics/latest/APIReference/API_DescribeCanaries.html DescribeCanaries>.
startCanary_name :: Lens.Lens' StartCanary Prelude.Text
startCanary_name :: Lens' StartCanary Text
startCanary_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCanary' {Text
name :: Text
$sel:name:StartCanary' :: StartCanary -> Text
name} -> Text
name) (\s :: StartCanary
s@StartCanary' {} Text
a -> StartCanary
s {$sel:name:StartCanary' :: Text
name = Text
a} :: StartCanary)

instance Core.AWSRequest StartCanary where
  type AWSResponse StartCanary = StartCanaryResponse
  request :: (Service -> Service) -> StartCanary -> Request StartCanary
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 StartCanary
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartCanary)))
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 -> StartCanaryResponse
StartCanaryResponse'
            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 StartCanary where
  hashWithSalt :: Int -> StartCanary -> Int
hashWithSalt Int
_salt StartCanary' {Text
name :: Text
$sel:name:StartCanary' :: StartCanary -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders StartCanary where
  toHeaders :: StartCanary -> 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.ToJSON StartCanary where
  toJSON :: StartCanary -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath StartCanary where
  toPath :: StartCanary -> ByteString
toPath StartCanary' {Text
name :: Text
$sel:name:StartCanary' :: StartCanary -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/canary/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name, ByteString
"/start"]

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

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

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

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

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