{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- |
-- Module      : Gogol.URLShortener.Url.Insert
-- Copyright   : (c) 2015-2025 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay <brendan.g.hay+gogol@gmail.com>
--               Toni Cebrián <toni@tonicebrian.com>
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new short URL.
--
-- /See:/ <https://developers.google.com/url-shortener/v1/getting_started URL Shortener API Reference> for @urlshortener.url.insert@.
module Gogol.URLShortener.Url.Insert
  ( -- * Resource
    URLShortenerUrlInsertResource,

    -- ** Constructing a Request
    URLShortenerUrlInsert (..),
    newURLShortenerUrlInsert,
  )
where

import Gogol.Prelude qualified as Core
import Gogol.URLShortener.Types

-- | A resource alias for @urlshortener.url.insert@ method which the
-- 'URLShortenerUrlInsert' request conforms to.
type URLShortenerUrlInsertResource =
  "urlshortener"
    Core.:> "v1"
    Core.:> "url"
    Core.:> Core.QueryParam "alt" Core.AltJSON
    Core.:> Core.ReqBody '[Core.JSON] Url
    Core.:> Core.Post '[Core.JSON] Url

-- | Creates a new short URL.
--
-- /See:/ 'newURLShortenerUrlInsert' smart constructor.
newtype URLShortenerUrlInsert = URLShortenerUrlInsert
  { -- | Multipart request metadata.
    URLShortenerUrlInsert -> Url
payload :: Url
  }
  deriving (URLShortenerUrlInsert -> URLShortenerUrlInsert -> Bool
(URLShortenerUrlInsert -> URLShortenerUrlInsert -> Bool)
-> (URLShortenerUrlInsert -> URLShortenerUrlInsert -> Bool)
-> Eq URLShortenerUrlInsert
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: URLShortenerUrlInsert -> URLShortenerUrlInsert -> Bool
== :: URLShortenerUrlInsert -> URLShortenerUrlInsert -> Bool
$c/= :: URLShortenerUrlInsert -> URLShortenerUrlInsert -> Bool
/= :: URLShortenerUrlInsert -> URLShortenerUrlInsert -> Bool
Core.Eq, Int -> URLShortenerUrlInsert -> ShowS
[URLShortenerUrlInsert] -> ShowS
URLShortenerUrlInsert -> String
(Int -> URLShortenerUrlInsert -> ShowS)
-> (URLShortenerUrlInsert -> String)
-> ([URLShortenerUrlInsert] -> ShowS)
-> Show URLShortenerUrlInsert
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> URLShortenerUrlInsert -> ShowS
showsPrec :: Int -> URLShortenerUrlInsert -> ShowS
$cshow :: URLShortenerUrlInsert -> String
show :: URLShortenerUrlInsert -> String
$cshowList :: [URLShortenerUrlInsert] -> ShowS
showList :: [URLShortenerUrlInsert] -> ShowS
Core.Show, (forall x. URLShortenerUrlInsert -> Rep URLShortenerUrlInsert x)
-> (forall x. Rep URLShortenerUrlInsert x -> URLShortenerUrlInsert)
-> Generic URLShortenerUrlInsert
forall x. Rep URLShortenerUrlInsert x -> URLShortenerUrlInsert
forall x. URLShortenerUrlInsert -> Rep URLShortenerUrlInsert x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. URLShortenerUrlInsert -> Rep URLShortenerUrlInsert x
from :: forall x. URLShortenerUrlInsert -> Rep URLShortenerUrlInsert x
$cto :: forall x. Rep URLShortenerUrlInsert x -> URLShortenerUrlInsert
to :: forall x. Rep URLShortenerUrlInsert x -> URLShortenerUrlInsert
Core.Generic)

-- | Creates a value of 'URLShortenerUrlInsert' with the minimum fields required to make a request.
newURLShortenerUrlInsert ::
  -- |  Multipart request metadata. See 'payload'.
  Url ->
  URLShortenerUrlInsert
newURLShortenerUrlInsert :: Url -> URLShortenerUrlInsert
newURLShortenerUrlInsert Url
payload =
  URLShortenerUrlInsert {payload :: Url
payload = Url
payload}

instance Core.GoogleRequest URLShortenerUrlInsert where
  type Rs URLShortenerUrlInsert = Url
  type Scopes URLShortenerUrlInsert = '[Urlshortener'FullControl]
  requestClient :: URLShortenerUrlInsert -> GClient (Rs URLShortenerUrlInsert)
requestClient URLShortenerUrlInsert {Url
payload :: URLShortenerUrlInsert -> Url
payload :: Url
..} =
    Maybe AltJSON -> Url -> ServiceConfig -> GClient Url
go (AltJSON -> Maybe AltJSON
forall a. a -> Maybe a
Core.Just AltJSON
Core.AltJSON) Url
payload ServiceConfig
uRLShortenerService
    where
      go :: Fn URLShortenerUrlInsertResource
go =
        Proxy URLShortenerUrlInsertResource
-> Request -> Fn URLShortenerUrlInsertResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
          (Proxy URLShortenerUrlInsertResource
forall {k} (t :: k). Proxy t
Core.Proxy :: Core.Proxy URLShortenerUrlInsertResource)
          Request
forall a. Monoid a => a
Core.mempty