{-# 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.IoTWireless.GetServiceProfile
(
GetServiceProfile (..),
newGetServiceProfile,
getServiceProfile_id,
GetServiceProfileResponse (..),
newGetServiceProfileResponse,
getServiceProfileResponse_arn,
getServiceProfileResponse_id,
getServiceProfileResponse_loRaWAN,
getServiceProfileResponse_name,
getServiceProfileResponse_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
data GetServiceProfile = GetServiceProfile'
{
GetServiceProfile -> Text
id :: Prelude.Text
}
deriving (GetServiceProfile -> GetServiceProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceProfile -> GetServiceProfile -> Bool
$c/= :: GetServiceProfile -> GetServiceProfile -> Bool
== :: GetServiceProfile -> GetServiceProfile -> Bool
$c== :: GetServiceProfile -> GetServiceProfile -> Bool
Prelude.Eq, ReadPrec [GetServiceProfile]
ReadPrec GetServiceProfile
Int -> ReadS GetServiceProfile
ReadS [GetServiceProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetServiceProfile]
$creadListPrec :: ReadPrec [GetServiceProfile]
readPrec :: ReadPrec GetServiceProfile
$creadPrec :: ReadPrec GetServiceProfile
readList :: ReadS [GetServiceProfile]
$creadList :: ReadS [GetServiceProfile]
readsPrec :: Int -> ReadS GetServiceProfile
$creadsPrec :: Int -> ReadS GetServiceProfile
Prelude.Read, Int -> GetServiceProfile -> ShowS
[GetServiceProfile] -> ShowS
GetServiceProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceProfile] -> ShowS
$cshowList :: [GetServiceProfile] -> ShowS
show :: GetServiceProfile -> String
$cshow :: GetServiceProfile -> String
showsPrec :: Int -> GetServiceProfile -> ShowS
$cshowsPrec :: Int -> GetServiceProfile -> ShowS
Prelude.Show, forall x. Rep GetServiceProfile x -> GetServiceProfile
forall x. GetServiceProfile -> Rep GetServiceProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetServiceProfile x -> GetServiceProfile
$cfrom :: forall x. GetServiceProfile -> Rep GetServiceProfile x
Prelude.Generic)
newGetServiceProfile ::
Prelude.Text ->
GetServiceProfile
newGetServiceProfile :: Text -> GetServiceProfile
newGetServiceProfile Text
pId_ =
GetServiceProfile' {$sel:id:GetServiceProfile' :: Text
id = Text
pId_}
getServiceProfile_id :: Lens.Lens' GetServiceProfile Prelude.Text
getServiceProfile_id :: Lens' GetServiceProfile Text
getServiceProfile_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceProfile' {Text
id :: Text
$sel:id:GetServiceProfile' :: GetServiceProfile -> Text
id} -> Text
id) (\s :: GetServiceProfile
s@GetServiceProfile' {} Text
a -> GetServiceProfile
s {$sel:id:GetServiceProfile' :: Text
id = Text
a} :: GetServiceProfile)
instance Core.AWSRequest GetServiceProfile where
type
AWSResponse GetServiceProfile =
GetServiceProfileResponse
request :: (Service -> Service)
-> GetServiceProfile -> Request GetServiceProfile
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetServiceProfile
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse GetServiceProfile)))
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
-> Maybe LoRaWANGetServiceProfileInfo
-> Maybe Text
-> Int
-> GetServiceProfileResponse
GetServiceProfileResponse'
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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LoRaWAN")
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
"Name")
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 GetServiceProfile where
hashWithSalt :: Int -> GetServiceProfile -> Int
hashWithSalt Int
_salt GetServiceProfile' {Text
id :: Text
$sel:id:GetServiceProfile' :: GetServiceProfile -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
instance Prelude.NFData GetServiceProfile where
rnf :: GetServiceProfile -> ()
rnf GetServiceProfile' {Text
id :: Text
$sel:id:GetServiceProfile' :: GetServiceProfile -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
id
instance Data.ToHeaders GetServiceProfile where
toHeaders :: GetServiceProfile -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath GetServiceProfile where
toPath :: GetServiceProfile -> ByteString
toPath GetServiceProfile' {Text
id :: Text
$sel:id:GetServiceProfile' :: GetServiceProfile -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/service-profiles/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]
instance Data.ToQuery GetServiceProfile where
toQuery :: GetServiceProfile -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetServiceProfileResponse = GetServiceProfileResponse'
{
GetServiceProfileResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
GetServiceProfileResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
GetServiceProfileResponse -> Maybe LoRaWANGetServiceProfileInfo
loRaWAN :: Prelude.Maybe LoRaWANGetServiceProfileInfo,
GetServiceProfileResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
GetServiceProfileResponse -> Int
httpStatus :: Prelude.Int
}
deriving (GetServiceProfileResponse -> GetServiceProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceProfileResponse -> GetServiceProfileResponse -> Bool
$c/= :: GetServiceProfileResponse -> GetServiceProfileResponse -> Bool
== :: GetServiceProfileResponse -> GetServiceProfileResponse -> Bool
$c== :: GetServiceProfileResponse -> GetServiceProfileResponse -> Bool
Prelude.Eq, ReadPrec [GetServiceProfileResponse]
ReadPrec GetServiceProfileResponse
Int -> ReadS GetServiceProfileResponse
ReadS [GetServiceProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetServiceProfileResponse]
$creadListPrec :: ReadPrec [GetServiceProfileResponse]
readPrec :: ReadPrec GetServiceProfileResponse
$creadPrec :: ReadPrec GetServiceProfileResponse
readList :: ReadS [GetServiceProfileResponse]
$creadList :: ReadS [GetServiceProfileResponse]
readsPrec :: Int -> ReadS GetServiceProfileResponse
$creadsPrec :: Int -> ReadS GetServiceProfileResponse
Prelude.Read, Int -> GetServiceProfileResponse -> ShowS
[GetServiceProfileResponse] -> ShowS
GetServiceProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceProfileResponse] -> ShowS
$cshowList :: [GetServiceProfileResponse] -> ShowS
show :: GetServiceProfileResponse -> String
$cshow :: GetServiceProfileResponse -> String
showsPrec :: Int -> GetServiceProfileResponse -> ShowS
$cshowsPrec :: Int -> GetServiceProfileResponse -> ShowS
Prelude.Show, forall x.
Rep GetServiceProfileResponse x -> GetServiceProfileResponse
forall x.
GetServiceProfileResponse -> Rep GetServiceProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetServiceProfileResponse x -> GetServiceProfileResponse
$cfrom :: forall x.
GetServiceProfileResponse -> Rep GetServiceProfileResponse x
Prelude.Generic)
newGetServiceProfileResponse ::
Prelude.Int ->
GetServiceProfileResponse
newGetServiceProfileResponse :: Int -> GetServiceProfileResponse
newGetServiceProfileResponse Int
pHttpStatus_ =
GetServiceProfileResponse'
{ $sel:arn:GetServiceProfileResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
$sel:id:GetServiceProfileResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
$sel:loRaWAN:GetServiceProfileResponse' :: Maybe LoRaWANGetServiceProfileInfo
loRaWAN = forall a. Maybe a
Prelude.Nothing,
$sel:name:GetServiceProfileResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetServiceProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
}
getServiceProfileResponse_arn :: Lens.Lens' GetServiceProfileResponse (Prelude.Maybe Prelude.Text)
getServiceProfileResponse_arn :: Lens' GetServiceProfileResponse (Maybe Text)
getServiceProfileResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceProfileResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetServiceProfileResponse' :: GetServiceProfileResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetServiceProfileResponse
s@GetServiceProfileResponse' {} Maybe Text
a -> GetServiceProfileResponse
s {$sel:arn:GetServiceProfileResponse' :: Maybe Text
arn = Maybe Text
a} :: GetServiceProfileResponse)
getServiceProfileResponse_id :: Lens.Lens' GetServiceProfileResponse (Prelude.Maybe Prelude.Text)
getServiceProfileResponse_id :: Lens' GetServiceProfileResponse (Maybe Text)
getServiceProfileResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceProfileResponse' {Maybe Text
id :: Maybe Text
$sel:id:GetServiceProfileResponse' :: GetServiceProfileResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: GetServiceProfileResponse
s@GetServiceProfileResponse' {} Maybe Text
a -> GetServiceProfileResponse
s {$sel:id:GetServiceProfileResponse' :: Maybe Text
id = Maybe Text
a} :: GetServiceProfileResponse)
getServiceProfileResponse_loRaWAN :: Lens.Lens' GetServiceProfileResponse (Prelude.Maybe LoRaWANGetServiceProfileInfo)
getServiceProfileResponse_loRaWAN :: Lens'
GetServiceProfileResponse (Maybe LoRaWANGetServiceProfileInfo)
getServiceProfileResponse_loRaWAN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceProfileResponse' {Maybe LoRaWANGetServiceProfileInfo
loRaWAN :: Maybe LoRaWANGetServiceProfileInfo
$sel:loRaWAN:GetServiceProfileResponse' :: GetServiceProfileResponse -> Maybe LoRaWANGetServiceProfileInfo
loRaWAN} -> Maybe LoRaWANGetServiceProfileInfo
loRaWAN) (\s :: GetServiceProfileResponse
s@GetServiceProfileResponse' {} Maybe LoRaWANGetServiceProfileInfo
a -> GetServiceProfileResponse
s {$sel:loRaWAN:GetServiceProfileResponse' :: Maybe LoRaWANGetServiceProfileInfo
loRaWAN = Maybe LoRaWANGetServiceProfileInfo
a} :: GetServiceProfileResponse)
getServiceProfileResponse_name :: Lens.Lens' GetServiceProfileResponse (Prelude.Maybe Prelude.Text)
getServiceProfileResponse_name :: Lens' GetServiceProfileResponse (Maybe Text)
getServiceProfileResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceProfileResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetServiceProfileResponse' :: GetServiceProfileResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetServiceProfileResponse
s@GetServiceProfileResponse' {} Maybe Text
a -> GetServiceProfileResponse
s {$sel:name:GetServiceProfileResponse' :: Maybe Text
name = Maybe Text
a} :: GetServiceProfileResponse)
getServiceProfileResponse_httpStatus :: Lens.Lens' GetServiceProfileResponse Prelude.Int
getServiceProfileResponse_httpStatus :: Lens' GetServiceProfileResponse Int
getServiceProfileResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceProfileResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetServiceProfileResponse' :: GetServiceProfileResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetServiceProfileResponse
s@GetServiceProfileResponse' {} Int
a -> GetServiceProfileResponse
s {$sel:httpStatus:GetServiceProfileResponse' :: Int
httpStatus = Int
a} :: GetServiceProfileResponse)
instance Prelude.NFData GetServiceProfileResponse where
rnf :: GetServiceProfileResponse -> ()
rnf GetServiceProfileResponse' {Int
Maybe Text
Maybe LoRaWANGetServiceProfileInfo
httpStatus :: Int
name :: Maybe Text
loRaWAN :: Maybe LoRaWANGetServiceProfileInfo
id :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:GetServiceProfileResponse' :: GetServiceProfileResponse -> Int
$sel:name:GetServiceProfileResponse' :: GetServiceProfileResponse -> Maybe Text
$sel:loRaWAN:GetServiceProfileResponse' :: GetServiceProfileResponse -> Maybe LoRaWANGetServiceProfileInfo
$sel:id:GetServiceProfileResponse' :: GetServiceProfileResponse -> Maybe Text
$sel:arn:GetServiceProfileResponse' :: GetServiceProfileResponse -> 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 Maybe LoRaWANGetServiceProfileInfo
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 Int
httpStatus