{-# 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 #-}
module Amazonka.SageMaker.CreateEndpoint
  ( 
    CreateEndpoint (..),
    newCreateEndpoint,
    
    createEndpoint_deploymentConfig,
    createEndpoint_tags,
    createEndpoint_endpointName,
    createEndpoint_endpointConfigName,
    
    CreateEndpointResponse (..),
    newCreateEndpointResponse,
    
    createEndpointResponse_httpStatus,
    createEndpointResponse_endpointArn,
  )
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.SageMaker.Types
data CreateEndpoint = CreateEndpoint'
  { CreateEndpoint -> Maybe DeploymentConfig
deploymentConfig :: Prelude.Maybe DeploymentConfig,
    
    
    
    
    CreateEndpoint -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    
    
    
    
    CreateEndpoint -> Text
endpointName :: Prelude.Text,
    
    
    CreateEndpoint -> Text
endpointConfigName :: Prelude.Text
  }
  deriving (CreateEndpoint -> CreateEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEndpoint -> CreateEndpoint -> Bool
$c/= :: CreateEndpoint -> CreateEndpoint -> Bool
== :: CreateEndpoint -> CreateEndpoint -> Bool
$c== :: CreateEndpoint -> CreateEndpoint -> Bool
Prelude.Eq, ReadPrec [CreateEndpoint]
ReadPrec CreateEndpoint
Int -> ReadS CreateEndpoint
ReadS [CreateEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEndpoint]
$creadListPrec :: ReadPrec [CreateEndpoint]
readPrec :: ReadPrec CreateEndpoint
$creadPrec :: ReadPrec CreateEndpoint
readList :: ReadS [CreateEndpoint]
$creadList :: ReadS [CreateEndpoint]
readsPrec :: Int -> ReadS CreateEndpoint
$creadsPrec :: Int -> ReadS CreateEndpoint
Prelude.Read, Int -> CreateEndpoint -> ShowS
[CreateEndpoint] -> ShowS
CreateEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEndpoint] -> ShowS
$cshowList :: [CreateEndpoint] -> ShowS
show :: CreateEndpoint -> String
$cshow :: CreateEndpoint -> String
showsPrec :: Int -> CreateEndpoint -> ShowS
$cshowsPrec :: Int -> CreateEndpoint -> ShowS
Prelude.Show, forall x. Rep CreateEndpoint x -> CreateEndpoint
forall x. CreateEndpoint -> Rep CreateEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateEndpoint x -> CreateEndpoint
$cfrom :: forall x. CreateEndpoint -> Rep CreateEndpoint x
Prelude.Generic)
newCreateEndpoint ::
  
  Prelude.Text ->
  
  Prelude.Text ->
  CreateEndpoint
newCreateEndpoint :: Text -> Text -> CreateEndpoint
newCreateEndpoint Text
pEndpointName_ Text
pEndpointConfigName_ =
  CreateEndpoint'
    { $sel:deploymentConfig:CreateEndpoint' :: Maybe DeploymentConfig
deploymentConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateEndpoint' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointName:CreateEndpoint' :: Text
endpointName = Text
pEndpointName_,
      $sel:endpointConfigName:CreateEndpoint' :: Text
endpointConfigName = Text
pEndpointConfigName_
    }
createEndpoint_deploymentConfig :: Lens.Lens' CreateEndpoint (Prelude.Maybe DeploymentConfig)
createEndpoint_deploymentConfig :: Lens' CreateEndpoint (Maybe DeploymentConfig)
createEndpoint_deploymentConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Maybe DeploymentConfig
deploymentConfig :: Maybe DeploymentConfig
$sel:deploymentConfig:CreateEndpoint' :: CreateEndpoint -> Maybe DeploymentConfig
deploymentConfig} -> Maybe DeploymentConfig
deploymentConfig) (\s :: CreateEndpoint
s@CreateEndpoint' {} Maybe DeploymentConfig
a -> CreateEndpoint
s {$sel:deploymentConfig:CreateEndpoint' :: Maybe DeploymentConfig
deploymentConfig = Maybe DeploymentConfig
a} :: CreateEndpoint)
createEndpoint_tags :: Lens.Lens' CreateEndpoint (Prelude.Maybe [Tag])
createEndpoint_tags :: Lens' CreateEndpoint (Maybe [Tag])
createEndpoint_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateEndpoint' :: CreateEndpoint -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateEndpoint
s@CreateEndpoint' {} Maybe [Tag]
a -> CreateEndpoint
s {$sel:tags:CreateEndpoint' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateEndpoint) 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
createEndpoint_endpointName :: Lens.Lens' CreateEndpoint Prelude.Text
createEndpoint_endpointName :: Lens' CreateEndpoint Text
createEndpoint_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Text
endpointName :: Text
$sel:endpointName:CreateEndpoint' :: CreateEndpoint -> Text
endpointName} -> Text
endpointName) (\s :: CreateEndpoint
s@CreateEndpoint' {} Text
a -> CreateEndpoint
s {$sel:endpointName:CreateEndpoint' :: Text
endpointName = Text
a} :: CreateEndpoint)
createEndpoint_endpointConfigName :: Lens.Lens' CreateEndpoint Prelude.Text
createEndpoint_endpointConfigName :: Lens' CreateEndpoint Text
createEndpoint_endpointConfigName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpoint' {Text
endpointConfigName :: Text
$sel:endpointConfigName:CreateEndpoint' :: CreateEndpoint -> Text
endpointConfigName} -> Text
endpointConfigName) (\s :: CreateEndpoint
s@CreateEndpoint' {} Text
a -> CreateEndpoint
s {$sel:endpointConfigName:CreateEndpoint' :: Text
endpointConfigName = Text
a} :: CreateEndpoint)
instance Core.AWSRequest CreateEndpoint where
  type
    AWSResponse CreateEndpoint =
      CreateEndpointResponse
  request :: (Service -> Service) -> CreateEndpoint -> Request CreateEndpoint
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 CreateEndpoint
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateEndpoint)))
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 ->
          Int -> Text -> CreateEndpointResponse
CreateEndpointResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"EndpointArn")
      )
instance Prelude.Hashable CreateEndpoint where
  hashWithSalt :: Int -> CreateEndpoint -> Int
hashWithSalt Int
_salt CreateEndpoint' {Maybe [Tag]
Maybe DeploymentConfig
Text
endpointConfigName :: Text
endpointName :: Text
tags :: Maybe [Tag]
deploymentConfig :: Maybe DeploymentConfig
$sel:endpointConfigName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:endpointName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:tags:CreateEndpoint' :: CreateEndpoint -> Maybe [Tag]
$sel:deploymentConfig:CreateEndpoint' :: CreateEndpoint -> Maybe DeploymentConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeploymentConfig
deploymentConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointConfigName
instance Prelude.NFData CreateEndpoint where
  rnf :: CreateEndpoint -> ()
rnf CreateEndpoint' {Maybe [Tag]
Maybe DeploymentConfig
Text
endpointConfigName :: Text
endpointName :: Text
tags :: Maybe [Tag]
deploymentConfig :: Maybe DeploymentConfig
$sel:endpointConfigName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:endpointName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:tags:CreateEndpoint' :: CreateEndpoint -> Maybe [Tag]
$sel:deploymentConfig:CreateEndpoint' :: CreateEndpoint -> Maybe DeploymentConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DeploymentConfig
deploymentConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
endpointName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointConfigName
instance Data.ToHeaders CreateEndpoint where
  toHeaders :: CreateEndpoint -> 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
"SageMaker.CreateEndpoint" :: 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 CreateEndpoint where
  toJSON :: CreateEndpoint -> Value
toJSON CreateEndpoint' {Maybe [Tag]
Maybe DeploymentConfig
Text
endpointConfigName :: Text
endpointName :: Text
tags :: Maybe [Tag]
deploymentConfig :: Maybe DeploymentConfig
$sel:endpointConfigName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:endpointName:CreateEndpoint' :: CreateEndpoint -> Text
$sel:tags:CreateEndpoint' :: CreateEndpoint -> Maybe [Tag]
$sel:deploymentConfig:CreateEndpoint' :: CreateEndpoint -> Maybe DeploymentConfig
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DeploymentConfig" 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 DeploymentConfig
deploymentConfig,
            (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
"EndpointName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"EndpointConfigName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointConfigName)
          ]
      )
instance Data.ToPath CreateEndpoint where
  toPath :: CreateEndpoint -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CreateEndpoint where
  toQuery :: CreateEndpoint -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CreateEndpointResponse = CreateEndpointResponse'
  { 
    CreateEndpointResponse -> Int
httpStatus :: Prelude.Int,
    
    CreateEndpointResponse -> Text
endpointArn :: Prelude.Text
  }
  deriving (CreateEndpointResponse -> CreateEndpointResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEndpointResponse -> CreateEndpointResponse -> Bool
$c/= :: CreateEndpointResponse -> CreateEndpointResponse -> Bool
== :: CreateEndpointResponse -> CreateEndpointResponse -> Bool
$c== :: CreateEndpointResponse -> CreateEndpointResponse -> Bool
Prelude.Eq, ReadPrec [CreateEndpointResponse]
ReadPrec CreateEndpointResponse
Int -> ReadS CreateEndpointResponse
ReadS [CreateEndpointResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEndpointResponse]
$creadListPrec :: ReadPrec [CreateEndpointResponse]
readPrec :: ReadPrec CreateEndpointResponse
$creadPrec :: ReadPrec CreateEndpointResponse
readList :: ReadS [CreateEndpointResponse]
$creadList :: ReadS [CreateEndpointResponse]
readsPrec :: Int -> ReadS CreateEndpointResponse
$creadsPrec :: Int -> ReadS CreateEndpointResponse
Prelude.Read, Int -> CreateEndpointResponse -> ShowS
[CreateEndpointResponse] -> ShowS
CreateEndpointResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEndpointResponse] -> ShowS
$cshowList :: [CreateEndpointResponse] -> ShowS
show :: CreateEndpointResponse -> String
$cshow :: CreateEndpointResponse -> String
showsPrec :: Int -> CreateEndpointResponse -> ShowS
$cshowsPrec :: Int -> CreateEndpointResponse -> ShowS
Prelude.Show, forall x. Rep CreateEndpointResponse x -> CreateEndpointResponse
forall x. CreateEndpointResponse -> Rep CreateEndpointResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateEndpointResponse x -> CreateEndpointResponse
$cfrom :: forall x. CreateEndpointResponse -> Rep CreateEndpointResponse x
Prelude.Generic)
newCreateEndpointResponse ::
  
  Prelude.Int ->
  
  Prelude.Text ->
  CreateEndpointResponse
newCreateEndpointResponse :: Int -> Text -> CreateEndpointResponse
newCreateEndpointResponse Int
pHttpStatus_ Text
pEndpointArn_ =
  CreateEndpointResponse'
    { $sel:httpStatus:CreateEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:endpointArn:CreateEndpointResponse' :: Text
endpointArn = Text
pEndpointArn_
    }
createEndpointResponse_httpStatus :: Lens.Lens' CreateEndpointResponse Prelude.Int
createEndpointResponse_httpStatus :: Lens' CreateEndpointResponse Int
createEndpointResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateEndpointResponse' :: CreateEndpointResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateEndpointResponse
s@CreateEndpointResponse' {} Int
a -> CreateEndpointResponse
s {$sel:httpStatus:CreateEndpointResponse' :: Int
httpStatus = Int
a} :: CreateEndpointResponse)
createEndpointResponse_endpointArn :: Lens.Lens' CreateEndpointResponse Prelude.Text
createEndpointResponse_endpointArn :: Lens' CreateEndpointResponse Text
createEndpointResponse_endpointArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEndpointResponse' {Text
endpointArn :: Text
$sel:endpointArn:CreateEndpointResponse' :: CreateEndpointResponse -> Text
endpointArn} -> Text
endpointArn) (\s :: CreateEndpointResponse
s@CreateEndpointResponse' {} Text
a -> CreateEndpointResponse
s {$sel:endpointArn:CreateEndpointResponse' :: Text
endpointArn = Text
a} :: CreateEndpointResponse)
instance Prelude.NFData CreateEndpointResponse where
  rnf :: CreateEndpointResponse -> ()
rnf CreateEndpointResponse' {Int
Text
endpointArn :: Text
httpStatus :: Int
$sel:endpointArn:CreateEndpointResponse' :: CreateEndpointResponse -> Text
$sel:httpStatus:CreateEndpointResponse' :: CreateEndpointResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointArn