{-# 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.IoTWireless.CreateServiceProfile
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new service profile.
module Amazonka.IoTWireless.CreateServiceProfile
  ( -- * Creating a Request
    CreateServiceProfile (..),
    newCreateServiceProfile,

    -- * Request Lenses
    createServiceProfile_clientRequestToken,
    createServiceProfile_loRaWAN,
    createServiceProfile_name,
    createServiceProfile_tags,

    -- * Destructuring the Response
    CreateServiceProfileResponse (..),
    newCreateServiceProfileResponse,

    -- * Response Lenses
    createServiceProfileResponse_arn,
    createServiceProfileResponse_id,
    createServiceProfileResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateServiceProfile' smart constructor.
data CreateServiceProfile = CreateServiceProfile'
  { -- | Each resource must have a unique client request token. If you try to
    -- create a new resource with the same token as a resource that already
    -- exists, an exception occurs. If you omit this value, AWS SDKs will
    -- automatically generate a unique client request.
    CreateServiceProfile -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The service profile information to use to create the service profile.
    CreateServiceProfile -> Maybe LoRaWANServiceProfile
loRaWAN :: Prelude.Maybe LoRaWANServiceProfile,
    -- | The name of the new resource.
    CreateServiceProfile -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The tags to attach to the new service profile. Tags are metadata that
    -- you can use to manage a resource.
    CreateServiceProfile -> Maybe [Tag]
tags :: Prelude.Maybe [Tag]
  }
  deriving (CreateServiceProfile -> CreateServiceProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateServiceProfile -> CreateServiceProfile -> Bool
$c/= :: CreateServiceProfile -> CreateServiceProfile -> Bool
== :: CreateServiceProfile -> CreateServiceProfile -> Bool
$c== :: CreateServiceProfile -> CreateServiceProfile -> Bool
Prelude.Eq, ReadPrec [CreateServiceProfile]
ReadPrec CreateServiceProfile
Int -> ReadS CreateServiceProfile
ReadS [CreateServiceProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateServiceProfile]
$creadListPrec :: ReadPrec [CreateServiceProfile]
readPrec :: ReadPrec CreateServiceProfile
$creadPrec :: ReadPrec CreateServiceProfile
readList :: ReadS [CreateServiceProfile]
$creadList :: ReadS [CreateServiceProfile]
readsPrec :: Int -> ReadS CreateServiceProfile
$creadsPrec :: Int -> ReadS CreateServiceProfile
Prelude.Read, Int -> CreateServiceProfile -> ShowS
[CreateServiceProfile] -> ShowS
CreateServiceProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateServiceProfile] -> ShowS
$cshowList :: [CreateServiceProfile] -> ShowS
show :: CreateServiceProfile -> String
$cshow :: CreateServiceProfile -> String
showsPrec :: Int -> CreateServiceProfile -> ShowS
$cshowsPrec :: Int -> CreateServiceProfile -> ShowS
Prelude.Show, forall x. Rep CreateServiceProfile x -> CreateServiceProfile
forall x. CreateServiceProfile -> Rep CreateServiceProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateServiceProfile x -> CreateServiceProfile
$cfrom :: forall x. CreateServiceProfile -> Rep CreateServiceProfile x
Prelude.Generic)

-- |
-- Create a value of 'CreateServiceProfile' 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:
--
-- 'clientRequestToken', 'createServiceProfile_clientRequestToken' - Each resource must have a unique client request token. If you try to
-- create a new resource with the same token as a resource that already
-- exists, an exception occurs. If you omit this value, AWS SDKs will
-- automatically generate a unique client request.
--
-- 'loRaWAN', 'createServiceProfile_loRaWAN' - The service profile information to use to create the service profile.
--
-- 'name', 'createServiceProfile_name' - The name of the new resource.
--
-- 'tags', 'createServiceProfile_tags' - The tags to attach to the new service profile. Tags are metadata that
-- you can use to manage a resource.
newCreateServiceProfile ::
  CreateServiceProfile
newCreateServiceProfile :: CreateServiceProfile
newCreateServiceProfile =
  CreateServiceProfile'
    { $sel:clientRequestToken:CreateServiceProfile' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:loRaWAN:CreateServiceProfile' :: Maybe LoRaWANServiceProfile
loRaWAN = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateServiceProfile' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateServiceProfile' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | Each resource must have a unique client request token. If you try to
-- create a new resource with the same token as a resource that already
-- exists, an exception occurs. If you omit this value, AWS SDKs will
-- automatically generate a unique client request.
createServiceProfile_clientRequestToken :: Lens.Lens' CreateServiceProfile (Prelude.Maybe Prelude.Text)
createServiceProfile_clientRequestToken :: Lens' CreateServiceProfile (Maybe Text)
createServiceProfile_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceProfile' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:CreateServiceProfile' :: CreateServiceProfile -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: CreateServiceProfile
s@CreateServiceProfile' {} Maybe Text
a -> CreateServiceProfile
s {$sel:clientRequestToken:CreateServiceProfile' :: Maybe Text
clientRequestToken = Maybe Text
a} :: CreateServiceProfile)

-- | The service profile information to use to create the service profile.
createServiceProfile_loRaWAN :: Lens.Lens' CreateServiceProfile (Prelude.Maybe LoRaWANServiceProfile)
createServiceProfile_loRaWAN :: Lens' CreateServiceProfile (Maybe LoRaWANServiceProfile)
createServiceProfile_loRaWAN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceProfile' {Maybe LoRaWANServiceProfile
loRaWAN :: Maybe LoRaWANServiceProfile
$sel:loRaWAN:CreateServiceProfile' :: CreateServiceProfile -> Maybe LoRaWANServiceProfile
loRaWAN} -> Maybe LoRaWANServiceProfile
loRaWAN) (\s :: CreateServiceProfile
s@CreateServiceProfile' {} Maybe LoRaWANServiceProfile
a -> CreateServiceProfile
s {$sel:loRaWAN:CreateServiceProfile' :: Maybe LoRaWANServiceProfile
loRaWAN = Maybe LoRaWANServiceProfile
a} :: CreateServiceProfile)

-- | The name of the new resource.
createServiceProfile_name :: Lens.Lens' CreateServiceProfile (Prelude.Maybe Prelude.Text)
createServiceProfile_name :: Lens' CreateServiceProfile (Maybe Text)
createServiceProfile_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceProfile' {Maybe Text
name :: Maybe Text
$sel:name:CreateServiceProfile' :: CreateServiceProfile -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateServiceProfile
s@CreateServiceProfile' {} Maybe Text
a -> CreateServiceProfile
s {$sel:name:CreateServiceProfile' :: Maybe Text
name = Maybe Text
a} :: CreateServiceProfile)

-- | The tags to attach to the new service profile. Tags are metadata that
-- you can use to manage a resource.
createServiceProfile_tags :: Lens.Lens' CreateServiceProfile (Prelude.Maybe [Tag])
createServiceProfile_tags :: Lens' CreateServiceProfile (Maybe [Tag])
createServiceProfile_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceProfile' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateServiceProfile' :: CreateServiceProfile -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateServiceProfile
s@CreateServiceProfile' {} Maybe [Tag]
a -> CreateServiceProfile
s {$sel:tags:CreateServiceProfile' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateServiceProfile) 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

instance Core.AWSRequest CreateServiceProfile where
  type
    AWSResponse CreateServiceProfile =
      CreateServiceProfileResponse
  request :: (Service -> Service)
-> CreateServiceProfile -> Request CreateServiceProfile
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 CreateServiceProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateServiceProfile)))
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 ->
          Maybe Text -> Maybe Text -> Int -> CreateServiceProfileResponse
CreateServiceProfileResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Id")
            forall (f :: * -> *) a b. Applicative f => 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 CreateServiceProfile where
  hashWithSalt :: Int -> CreateServiceProfile -> Int
hashWithSalt Int
_salt CreateServiceProfile' {Maybe [Tag]
Maybe Text
Maybe LoRaWANServiceProfile
tags :: Maybe [Tag]
name :: Maybe Text
loRaWAN :: Maybe LoRaWANServiceProfile
clientRequestToken :: Maybe Text
$sel:tags:CreateServiceProfile' :: CreateServiceProfile -> Maybe [Tag]
$sel:name:CreateServiceProfile' :: CreateServiceProfile -> Maybe Text
$sel:loRaWAN:CreateServiceProfile' :: CreateServiceProfile -> Maybe LoRaWANServiceProfile
$sel:clientRequestToken:CreateServiceProfile' :: CreateServiceProfile -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoRaWANServiceProfile
loRaWAN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags

instance Prelude.NFData CreateServiceProfile where
  rnf :: CreateServiceProfile -> ()
rnf CreateServiceProfile' {Maybe [Tag]
Maybe Text
Maybe LoRaWANServiceProfile
tags :: Maybe [Tag]
name :: Maybe Text
loRaWAN :: Maybe LoRaWANServiceProfile
clientRequestToken :: Maybe Text
$sel:tags:CreateServiceProfile' :: CreateServiceProfile -> Maybe [Tag]
$sel:name:CreateServiceProfile' :: CreateServiceProfile -> Maybe Text
$sel:loRaWAN:CreateServiceProfile' :: CreateServiceProfile -> Maybe LoRaWANServiceProfile
$sel:clientRequestToken:CreateServiceProfile' :: CreateServiceProfile -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoRaWANServiceProfile
loRaWAN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags

instance Data.ToHeaders CreateServiceProfile where
  toHeaders :: CreateServiceProfile -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CreateServiceProfile where
  toJSON :: CreateServiceProfile -> Value
toJSON CreateServiceProfile' {Maybe [Tag]
Maybe Text
Maybe LoRaWANServiceProfile
tags :: Maybe [Tag]
name :: Maybe Text
loRaWAN :: Maybe LoRaWANServiceProfile
clientRequestToken :: Maybe Text
$sel:tags:CreateServiceProfile' :: CreateServiceProfile -> Maybe [Tag]
$sel:name:CreateServiceProfile' :: CreateServiceProfile -> Maybe Text
$sel:loRaWAN:CreateServiceProfile' :: CreateServiceProfile -> Maybe LoRaWANServiceProfile
$sel:clientRequestToken:CreateServiceProfile' :: CreateServiceProfile -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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 Text
clientRequestToken,
            (Key
"LoRaWAN" 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 LoRaWANServiceProfile
loRaWAN,
            (Key
"Name" 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 Text
name,
            (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
          ]
      )

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

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

-- | /See:/ 'newCreateServiceProfileResponse' smart constructor.
data CreateServiceProfileResponse = CreateServiceProfileResponse'
  { -- | The Amazon Resource Name of the new resource.
    CreateServiceProfileResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the new service profile.
    CreateServiceProfileResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateServiceProfileResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateServiceProfileResponse
-> CreateServiceProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateServiceProfileResponse
-> CreateServiceProfileResponse -> Bool
$c/= :: CreateServiceProfileResponse
-> CreateServiceProfileResponse -> Bool
== :: CreateServiceProfileResponse
-> CreateServiceProfileResponse -> Bool
$c== :: CreateServiceProfileResponse
-> CreateServiceProfileResponse -> Bool
Prelude.Eq, ReadPrec [CreateServiceProfileResponse]
ReadPrec CreateServiceProfileResponse
Int -> ReadS CreateServiceProfileResponse
ReadS [CreateServiceProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateServiceProfileResponse]
$creadListPrec :: ReadPrec [CreateServiceProfileResponse]
readPrec :: ReadPrec CreateServiceProfileResponse
$creadPrec :: ReadPrec CreateServiceProfileResponse
readList :: ReadS [CreateServiceProfileResponse]
$creadList :: ReadS [CreateServiceProfileResponse]
readsPrec :: Int -> ReadS CreateServiceProfileResponse
$creadsPrec :: Int -> ReadS CreateServiceProfileResponse
Prelude.Read, Int -> CreateServiceProfileResponse -> ShowS
[CreateServiceProfileResponse] -> ShowS
CreateServiceProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateServiceProfileResponse] -> ShowS
$cshowList :: [CreateServiceProfileResponse] -> ShowS
show :: CreateServiceProfileResponse -> String
$cshow :: CreateServiceProfileResponse -> String
showsPrec :: Int -> CreateServiceProfileResponse -> ShowS
$cshowsPrec :: Int -> CreateServiceProfileResponse -> ShowS
Prelude.Show, forall x.
Rep CreateServiceProfileResponse x -> CreateServiceProfileResponse
forall x.
CreateServiceProfileResponse -> Rep CreateServiceProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateServiceProfileResponse x -> CreateServiceProfileResponse
$cfrom :: forall x.
CreateServiceProfileResponse -> Rep CreateServiceProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateServiceProfileResponse' 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:
--
-- 'arn', 'createServiceProfileResponse_arn' - The Amazon Resource Name of the new resource.
--
-- 'id', 'createServiceProfileResponse_id' - The ID of the new service profile.
--
-- 'httpStatus', 'createServiceProfileResponse_httpStatus' - The response's http status code.
newCreateServiceProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateServiceProfileResponse
newCreateServiceProfileResponse :: Int -> CreateServiceProfileResponse
newCreateServiceProfileResponse Int
pHttpStatus_ =
  CreateServiceProfileResponse'
    { $sel:arn:CreateServiceProfileResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:id:CreateServiceProfileResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateServiceProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name of the new resource.
createServiceProfileResponse_arn :: Lens.Lens' CreateServiceProfileResponse (Prelude.Maybe Prelude.Text)
createServiceProfileResponse_arn :: Lens' CreateServiceProfileResponse (Maybe Text)
createServiceProfileResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceProfileResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:CreateServiceProfileResponse' :: CreateServiceProfileResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: CreateServiceProfileResponse
s@CreateServiceProfileResponse' {} Maybe Text
a -> CreateServiceProfileResponse
s {$sel:arn:CreateServiceProfileResponse' :: Maybe Text
arn = Maybe Text
a} :: CreateServiceProfileResponse)

-- | The ID of the new service profile.
createServiceProfileResponse_id :: Lens.Lens' CreateServiceProfileResponse (Prelude.Maybe Prelude.Text)
createServiceProfileResponse_id :: Lens' CreateServiceProfileResponse (Maybe Text)
createServiceProfileResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceProfileResponse' {Maybe Text
id :: Maybe Text
$sel:id:CreateServiceProfileResponse' :: CreateServiceProfileResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: CreateServiceProfileResponse
s@CreateServiceProfileResponse' {} Maybe Text
a -> CreateServiceProfileResponse
s {$sel:id:CreateServiceProfileResponse' :: Maybe Text
id = Maybe Text
a} :: CreateServiceProfileResponse)

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

instance Prelude.NFData CreateServiceProfileResponse where
  rnf :: CreateServiceProfileResponse -> ()
rnf CreateServiceProfileResponse' {Int
Maybe Text
httpStatus :: Int
id :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:CreateServiceProfileResponse' :: CreateServiceProfileResponse -> Int
$sel:id:CreateServiceProfileResponse' :: CreateServiceProfileResponse -> Maybe Text
$sel:arn:CreateServiceProfileResponse' :: CreateServiceProfileResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus