{-# 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.Glue.StartCrawlerSchedule
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Changes the schedule state of the specified crawler to @SCHEDULED@,
-- unless the crawler is already running or the schedule state is already
-- @SCHEDULED@.
module Amazonka.Glue.StartCrawlerSchedule
  ( -- * Creating a Request
    StartCrawlerSchedule (..),
    newStartCrawlerSchedule,

    -- * Request Lenses
    startCrawlerSchedule_crawlerName,

    -- * Destructuring the Response
    StartCrawlerScheduleResponse (..),
    newStartCrawlerScheduleResponse,

    -- * Response Lenses
    startCrawlerScheduleResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newStartCrawlerSchedule' smart constructor.
data StartCrawlerSchedule = StartCrawlerSchedule'
  { -- | Name of the crawler to schedule.
    StartCrawlerSchedule -> Text
crawlerName :: Prelude.Text
  }
  deriving (StartCrawlerSchedule -> StartCrawlerSchedule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartCrawlerSchedule -> StartCrawlerSchedule -> Bool
$c/= :: StartCrawlerSchedule -> StartCrawlerSchedule -> Bool
== :: StartCrawlerSchedule -> StartCrawlerSchedule -> Bool
$c== :: StartCrawlerSchedule -> StartCrawlerSchedule -> Bool
Prelude.Eq, ReadPrec [StartCrawlerSchedule]
ReadPrec StartCrawlerSchedule
Int -> ReadS StartCrawlerSchedule
ReadS [StartCrawlerSchedule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartCrawlerSchedule]
$creadListPrec :: ReadPrec [StartCrawlerSchedule]
readPrec :: ReadPrec StartCrawlerSchedule
$creadPrec :: ReadPrec StartCrawlerSchedule
readList :: ReadS [StartCrawlerSchedule]
$creadList :: ReadS [StartCrawlerSchedule]
readsPrec :: Int -> ReadS StartCrawlerSchedule
$creadsPrec :: Int -> ReadS StartCrawlerSchedule
Prelude.Read, Int -> StartCrawlerSchedule -> ShowS
[StartCrawlerSchedule] -> ShowS
StartCrawlerSchedule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartCrawlerSchedule] -> ShowS
$cshowList :: [StartCrawlerSchedule] -> ShowS
show :: StartCrawlerSchedule -> String
$cshow :: StartCrawlerSchedule -> String
showsPrec :: Int -> StartCrawlerSchedule -> ShowS
$cshowsPrec :: Int -> StartCrawlerSchedule -> ShowS
Prelude.Show, forall x. Rep StartCrawlerSchedule x -> StartCrawlerSchedule
forall x. StartCrawlerSchedule -> Rep StartCrawlerSchedule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartCrawlerSchedule x -> StartCrawlerSchedule
$cfrom :: forall x. StartCrawlerSchedule -> Rep StartCrawlerSchedule x
Prelude.Generic)

-- |
-- Create a value of 'StartCrawlerSchedule' 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:
--
-- 'crawlerName', 'startCrawlerSchedule_crawlerName' - Name of the crawler to schedule.
newStartCrawlerSchedule ::
  -- | 'crawlerName'
  Prelude.Text ->
  StartCrawlerSchedule
newStartCrawlerSchedule :: Text -> StartCrawlerSchedule
newStartCrawlerSchedule Text
pCrawlerName_ =
  StartCrawlerSchedule' {$sel:crawlerName:StartCrawlerSchedule' :: Text
crawlerName = Text
pCrawlerName_}

-- | Name of the crawler to schedule.
startCrawlerSchedule_crawlerName :: Lens.Lens' StartCrawlerSchedule Prelude.Text
startCrawlerSchedule_crawlerName :: Lens' StartCrawlerSchedule Text
startCrawlerSchedule_crawlerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartCrawlerSchedule' {Text
crawlerName :: Text
$sel:crawlerName:StartCrawlerSchedule' :: StartCrawlerSchedule -> Text
crawlerName} -> Text
crawlerName) (\s :: StartCrawlerSchedule
s@StartCrawlerSchedule' {} Text
a -> StartCrawlerSchedule
s {$sel:crawlerName:StartCrawlerSchedule' :: Text
crawlerName = Text
a} :: StartCrawlerSchedule)

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

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

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

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

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

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

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

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

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