{-# 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.DeviceFarm.CreateDevicePool
-- 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 device pool.
module Amazonka.DeviceFarm.CreateDevicePool
  ( -- * Creating a Request
    CreateDevicePool (..),
    newCreateDevicePool,

    -- * Request Lenses
    createDevicePool_description,
    createDevicePool_maxDevices,
    createDevicePool_projectArn,
    createDevicePool_name,
    createDevicePool_rules,

    -- * Destructuring the Response
    CreateDevicePoolResponse (..),
    newCreateDevicePoolResponse,

    -- * Response Lenses
    createDevicePoolResponse_devicePool,
    createDevicePoolResponse_httpStatus,
  )
where

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

-- | Represents a request to the create device pool operation.
--
-- /See:/ 'newCreateDevicePool' smart constructor.
data CreateDevicePool = CreateDevicePool'
  { -- | The device pool\'s description.
    CreateDevicePool -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The number of devices that Device Farm can add to your device pool.
    -- Device Farm adds devices that are available and meet the criteria that
    -- you assign for the @rules@ parameter. Depending on how many devices meet
    -- these constraints, your device pool might contain fewer devices than the
    -- value for this parameter.
    --
    -- By specifying the maximum number of devices, you can control the costs
    -- that you incur by running tests.
    CreateDevicePool -> Maybe Int
maxDevices :: Prelude.Maybe Prelude.Int,
    -- | The ARN of the project for the device pool.
    CreateDevicePool -> Text
projectArn :: Prelude.Text,
    -- | The device pool\'s name.
    CreateDevicePool -> Text
name :: Prelude.Text,
    -- | The device pool\'s rules.
    CreateDevicePool -> [Rule]
rules :: [Rule]
  }
  deriving (CreateDevicePool -> CreateDevicePool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDevicePool -> CreateDevicePool -> Bool
$c/= :: CreateDevicePool -> CreateDevicePool -> Bool
== :: CreateDevicePool -> CreateDevicePool -> Bool
$c== :: CreateDevicePool -> CreateDevicePool -> Bool
Prelude.Eq, ReadPrec [CreateDevicePool]
ReadPrec CreateDevicePool
Int -> ReadS CreateDevicePool
ReadS [CreateDevicePool]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDevicePool]
$creadListPrec :: ReadPrec [CreateDevicePool]
readPrec :: ReadPrec CreateDevicePool
$creadPrec :: ReadPrec CreateDevicePool
readList :: ReadS [CreateDevicePool]
$creadList :: ReadS [CreateDevicePool]
readsPrec :: Int -> ReadS CreateDevicePool
$creadsPrec :: Int -> ReadS CreateDevicePool
Prelude.Read, Int -> CreateDevicePool -> ShowS
[CreateDevicePool] -> ShowS
CreateDevicePool -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDevicePool] -> ShowS
$cshowList :: [CreateDevicePool] -> ShowS
show :: CreateDevicePool -> String
$cshow :: CreateDevicePool -> String
showsPrec :: Int -> CreateDevicePool -> ShowS
$cshowsPrec :: Int -> CreateDevicePool -> ShowS
Prelude.Show, forall x. Rep CreateDevicePool x -> CreateDevicePool
forall x. CreateDevicePool -> Rep CreateDevicePool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateDevicePool x -> CreateDevicePool
$cfrom :: forall x. CreateDevicePool -> Rep CreateDevicePool x
Prelude.Generic)

-- |
-- Create a value of 'CreateDevicePool' 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:
--
-- 'description', 'createDevicePool_description' - The device pool\'s description.
--
-- 'maxDevices', 'createDevicePool_maxDevices' - The number of devices that Device Farm can add to your device pool.
-- Device Farm adds devices that are available and meet the criteria that
-- you assign for the @rules@ parameter. Depending on how many devices meet
-- these constraints, your device pool might contain fewer devices than the
-- value for this parameter.
--
-- By specifying the maximum number of devices, you can control the costs
-- that you incur by running tests.
--
-- 'projectArn', 'createDevicePool_projectArn' - The ARN of the project for the device pool.
--
-- 'name', 'createDevicePool_name' - The device pool\'s name.
--
-- 'rules', 'createDevicePool_rules' - The device pool\'s rules.
newCreateDevicePool ::
  -- | 'projectArn'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  CreateDevicePool
newCreateDevicePool :: Text -> Text -> CreateDevicePool
newCreateDevicePool Text
pProjectArn_ Text
pName_ =
  CreateDevicePool'
    { $sel:description:CreateDevicePool' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:maxDevices:CreateDevicePool' :: Maybe Int
maxDevices = forall a. Maybe a
Prelude.Nothing,
      $sel:projectArn:CreateDevicePool' :: Text
projectArn = Text
pProjectArn_,
      $sel:name:CreateDevicePool' :: Text
name = Text
pName_,
      $sel:rules:CreateDevicePool' :: [Rule]
rules = forall a. Monoid a => a
Prelude.mempty
    }

-- | The device pool\'s description.
createDevicePool_description :: Lens.Lens' CreateDevicePool (Prelude.Maybe Prelude.Text)
createDevicePool_description :: Lens' CreateDevicePool (Maybe Text)
createDevicePool_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevicePool' {Maybe Text
description :: Maybe Text
$sel:description:CreateDevicePool' :: CreateDevicePool -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateDevicePool
s@CreateDevicePool' {} Maybe Text
a -> CreateDevicePool
s {$sel:description:CreateDevicePool' :: Maybe Text
description = Maybe Text
a} :: CreateDevicePool)

-- | The number of devices that Device Farm can add to your device pool.
-- Device Farm adds devices that are available and meet the criteria that
-- you assign for the @rules@ parameter. Depending on how many devices meet
-- these constraints, your device pool might contain fewer devices than the
-- value for this parameter.
--
-- By specifying the maximum number of devices, you can control the costs
-- that you incur by running tests.
createDevicePool_maxDevices :: Lens.Lens' CreateDevicePool (Prelude.Maybe Prelude.Int)
createDevicePool_maxDevices :: Lens' CreateDevicePool (Maybe Int)
createDevicePool_maxDevices = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevicePool' {Maybe Int
maxDevices :: Maybe Int
$sel:maxDevices:CreateDevicePool' :: CreateDevicePool -> Maybe Int
maxDevices} -> Maybe Int
maxDevices) (\s :: CreateDevicePool
s@CreateDevicePool' {} Maybe Int
a -> CreateDevicePool
s {$sel:maxDevices:CreateDevicePool' :: Maybe Int
maxDevices = Maybe Int
a} :: CreateDevicePool)

-- | The ARN of the project for the device pool.
createDevicePool_projectArn :: Lens.Lens' CreateDevicePool Prelude.Text
createDevicePool_projectArn :: Lens' CreateDevicePool Text
createDevicePool_projectArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevicePool' {Text
projectArn :: Text
$sel:projectArn:CreateDevicePool' :: CreateDevicePool -> Text
projectArn} -> Text
projectArn) (\s :: CreateDevicePool
s@CreateDevicePool' {} Text
a -> CreateDevicePool
s {$sel:projectArn:CreateDevicePool' :: Text
projectArn = Text
a} :: CreateDevicePool)

-- | The device pool\'s name.
createDevicePool_name :: Lens.Lens' CreateDevicePool Prelude.Text
createDevicePool_name :: Lens' CreateDevicePool Text
createDevicePool_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevicePool' {Text
name :: Text
$sel:name:CreateDevicePool' :: CreateDevicePool -> Text
name} -> Text
name) (\s :: CreateDevicePool
s@CreateDevicePool' {} Text
a -> CreateDevicePool
s {$sel:name:CreateDevicePool' :: Text
name = Text
a} :: CreateDevicePool)

-- | The device pool\'s rules.
createDevicePool_rules :: Lens.Lens' CreateDevicePool [Rule]
createDevicePool_rules :: Lens' CreateDevicePool [Rule]
createDevicePool_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevicePool' {[Rule]
rules :: [Rule]
$sel:rules:CreateDevicePool' :: CreateDevicePool -> [Rule]
rules} -> [Rule]
rules) (\s :: CreateDevicePool
s@CreateDevicePool' {} [Rule]
a -> CreateDevicePool
s {$sel:rules:CreateDevicePool' :: [Rule]
rules = [Rule]
a} :: CreateDevicePool) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest CreateDevicePool where
  type
    AWSResponse CreateDevicePool =
      CreateDevicePoolResponse
  request :: (Service -> Service)
-> CreateDevicePool -> Request CreateDevicePool
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 CreateDevicePool
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateDevicePool)))
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 DevicePool -> Int -> CreateDevicePoolResponse
CreateDevicePoolResponse'
            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
"devicePool")
            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 CreateDevicePool where
  hashWithSalt :: Int -> CreateDevicePool -> Int
hashWithSalt Int
_salt CreateDevicePool' {[Rule]
Maybe Int
Maybe Text
Text
rules :: [Rule]
name :: Text
projectArn :: Text
maxDevices :: Maybe Int
description :: Maybe Text
$sel:rules:CreateDevicePool' :: CreateDevicePool -> [Rule]
$sel:name:CreateDevicePool' :: CreateDevicePool -> Text
$sel:projectArn:CreateDevicePool' :: CreateDevicePool -> Text
$sel:maxDevices:CreateDevicePool' :: CreateDevicePool -> Maybe Int
$sel:description:CreateDevicePool' :: CreateDevicePool -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxDevices
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Rule]
rules

instance Prelude.NFData CreateDevicePool where
  rnf :: CreateDevicePool -> ()
rnf CreateDevicePool' {[Rule]
Maybe Int
Maybe Text
Text
rules :: [Rule]
name :: Text
projectArn :: Text
maxDevices :: Maybe Int
description :: Maybe Text
$sel:rules:CreateDevicePool' :: CreateDevicePool -> [Rule]
$sel:name:CreateDevicePool' :: CreateDevicePool -> Text
$sel:projectArn:CreateDevicePool' :: CreateDevicePool -> Text
$sel:maxDevices:CreateDevicePool' :: CreateDevicePool -> Maybe Int
$sel:description:CreateDevicePool' :: CreateDevicePool -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxDevices
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Rule]
rules

instance Data.ToHeaders CreateDevicePool where
  toHeaders :: CreateDevicePool -> 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
"DeviceFarm_20150623.CreateDevicePool" ::
                          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 CreateDevicePool where
  toJSON :: CreateDevicePool -> Value
toJSON CreateDevicePool' {[Rule]
Maybe Int
Maybe Text
Text
rules :: [Rule]
name :: Text
projectArn :: Text
maxDevices :: Maybe Int
description :: Maybe Text
$sel:rules:CreateDevicePool' :: CreateDevicePool -> [Rule]
$sel:name:CreateDevicePool' :: CreateDevicePool -> Text
$sel:projectArn:CreateDevicePool' :: CreateDevicePool -> Text
$sel:maxDevices:CreateDevicePool' :: CreateDevicePool -> Maybe Int
$sel:description:CreateDevicePool' :: CreateDevicePool -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" 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
description,
            (Key
"maxDevices" 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 Int
maxDevices,
            forall a. a -> Maybe a
Prelude.Just (Key
"projectArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
projectArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"rules" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Rule]
rules)
          ]
      )

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

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

-- | Represents the result of a create device pool request.
--
-- /See:/ 'newCreateDevicePoolResponse' smart constructor.
data CreateDevicePoolResponse = CreateDevicePoolResponse'
  { -- | The newly created device pool.
    CreateDevicePoolResponse -> Maybe DevicePool
devicePool :: Prelude.Maybe DevicePool,
    -- | The response's http status code.
    CreateDevicePoolResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateDevicePoolResponse -> CreateDevicePoolResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDevicePoolResponse -> CreateDevicePoolResponse -> Bool
$c/= :: CreateDevicePoolResponse -> CreateDevicePoolResponse -> Bool
== :: CreateDevicePoolResponse -> CreateDevicePoolResponse -> Bool
$c== :: CreateDevicePoolResponse -> CreateDevicePoolResponse -> Bool
Prelude.Eq, ReadPrec [CreateDevicePoolResponse]
ReadPrec CreateDevicePoolResponse
Int -> ReadS CreateDevicePoolResponse
ReadS [CreateDevicePoolResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDevicePoolResponse]
$creadListPrec :: ReadPrec [CreateDevicePoolResponse]
readPrec :: ReadPrec CreateDevicePoolResponse
$creadPrec :: ReadPrec CreateDevicePoolResponse
readList :: ReadS [CreateDevicePoolResponse]
$creadList :: ReadS [CreateDevicePoolResponse]
readsPrec :: Int -> ReadS CreateDevicePoolResponse
$creadsPrec :: Int -> ReadS CreateDevicePoolResponse
Prelude.Read, Int -> CreateDevicePoolResponse -> ShowS
[CreateDevicePoolResponse] -> ShowS
CreateDevicePoolResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDevicePoolResponse] -> ShowS
$cshowList :: [CreateDevicePoolResponse] -> ShowS
show :: CreateDevicePoolResponse -> String
$cshow :: CreateDevicePoolResponse -> String
showsPrec :: Int -> CreateDevicePoolResponse -> ShowS
$cshowsPrec :: Int -> CreateDevicePoolResponse -> ShowS
Prelude.Show, forall x.
Rep CreateDevicePoolResponse x -> CreateDevicePoolResponse
forall x.
CreateDevicePoolResponse -> Rep CreateDevicePoolResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDevicePoolResponse x -> CreateDevicePoolResponse
$cfrom :: forall x.
CreateDevicePoolResponse -> Rep CreateDevicePoolResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateDevicePoolResponse' 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:
--
-- 'devicePool', 'createDevicePoolResponse_devicePool' - The newly created device pool.
--
-- 'httpStatus', 'createDevicePoolResponse_httpStatus' - The response's http status code.
newCreateDevicePoolResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDevicePoolResponse
newCreateDevicePoolResponse :: Int -> CreateDevicePoolResponse
newCreateDevicePoolResponse Int
pHttpStatus_ =
  CreateDevicePoolResponse'
    { $sel:devicePool:CreateDevicePoolResponse' :: Maybe DevicePool
devicePool =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDevicePoolResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The newly created device pool.
createDevicePoolResponse_devicePool :: Lens.Lens' CreateDevicePoolResponse (Prelude.Maybe DevicePool)
createDevicePoolResponse_devicePool :: Lens' CreateDevicePoolResponse (Maybe DevicePool)
createDevicePoolResponse_devicePool = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevicePoolResponse' {Maybe DevicePool
devicePool :: Maybe DevicePool
$sel:devicePool:CreateDevicePoolResponse' :: CreateDevicePoolResponse -> Maybe DevicePool
devicePool} -> Maybe DevicePool
devicePool) (\s :: CreateDevicePoolResponse
s@CreateDevicePoolResponse' {} Maybe DevicePool
a -> CreateDevicePoolResponse
s {$sel:devicePool:CreateDevicePoolResponse' :: Maybe DevicePool
devicePool = Maybe DevicePool
a} :: CreateDevicePoolResponse)

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

instance Prelude.NFData CreateDevicePoolResponse where
  rnf :: CreateDevicePoolResponse -> ()
rnf CreateDevicePoolResponse' {Int
Maybe DevicePool
httpStatus :: Int
devicePool :: Maybe DevicePool
$sel:httpStatus:CreateDevicePoolResponse' :: CreateDevicePoolResponse -> Int
$sel:devicePool:CreateDevicePoolResponse' :: CreateDevicePoolResponse -> Maybe DevicePool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DevicePool
devicePool
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus