{-# 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.IoTFleetWise.ImportDecoderManifest
-- 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 decoder manifest using your existing CAN DBC file from your
-- local device.
module Amazonka.IoTFleetWise.ImportDecoderManifest
  ( -- * Creating a Request
    ImportDecoderManifest (..),
    newImportDecoderManifest,

    -- * Request Lenses
    importDecoderManifest_name,
    importDecoderManifest_networkFileDefinitions,

    -- * Destructuring the Response
    ImportDecoderManifestResponse (..),
    newImportDecoderManifestResponse,

    -- * Response Lenses
    importDecoderManifestResponse_httpStatus,
    importDecoderManifestResponse_name,
    importDecoderManifestResponse_arn,
  )
where

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

-- | /See:/ 'newImportDecoderManifest' smart constructor.
data ImportDecoderManifest = ImportDecoderManifest'
  { -- | The name of the decoder manifest to import.
    ImportDecoderManifest -> Text
name :: Prelude.Text,
    -- | The file to load into an Amazon Web Services account.
    ImportDecoderManifest -> [NetworkFileDefinition]
networkFileDefinitions :: [NetworkFileDefinition]
  }
  deriving (ImportDecoderManifest -> ImportDecoderManifest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportDecoderManifest -> ImportDecoderManifest -> Bool
$c/= :: ImportDecoderManifest -> ImportDecoderManifest -> Bool
== :: ImportDecoderManifest -> ImportDecoderManifest -> Bool
$c== :: ImportDecoderManifest -> ImportDecoderManifest -> Bool
Prelude.Eq, ReadPrec [ImportDecoderManifest]
ReadPrec ImportDecoderManifest
Int -> ReadS ImportDecoderManifest
ReadS [ImportDecoderManifest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportDecoderManifest]
$creadListPrec :: ReadPrec [ImportDecoderManifest]
readPrec :: ReadPrec ImportDecoderManifest
$creadPrec :: ReadPrec ImportDecoderManifest
readList :: ReadS [ImportDecoderManifest]
$creadList :: ReadS [ImportDecoderManifest]
readsPrec :: Int -> ReadS ImportDecoderManifest
$creadsPrec :: Int -> ReadS ImportDecoderManifest
Prelude.Read, Int -> ImportDecoderManifest -> ShowS
[ImportDecoderManifest] -> ShowS
ImportDecoderManifest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportDecoderManifest] -> ShowS
$cshowList :: [ImportDecoderManifest] -> ShowS
show :: ImportDecoderManifest -> String
$cshow :: ImportDecoderManifest -> String
showsPrec :: Int -> ImportDecoderManifest -> ShowS
$cshowsPrec :: Int -> ImportDecoderManifest -> ShowS
Prelude.Show, forall x. Rep ImportDecoderManifest x -> ImportDecoderManifest
forall x. ImportDecoderManifest -> Rep ImportDecoderManifest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportDecoderManifest x -> ImportDecoderManifest
$cfrom :: forall x. ImportDecoderManifest -> Rep ImportDecoderManifest x
Prelude.Generic)

-- |
-- Create a value of 'ImportDecoderManifest' 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:
--
-- 'name', 'importDecoderManifest_name' - The name of the decoder manifest to import.
--
-- 'networkFileDefinitions', 'importDecoderManifest_networkFileDefinitions' - The file to load into an Amazon Web Services account.
newImportDecoderManifest ::
  -- | 'name'
  Prelude.Text ->
  ImportDecoderManifest
newImportDecoderManifest :: Text -> ImportDecoderManifest
newImportDecoderManifest Text
pName_ =
  ImportDecoderManifest'
    { $sel:name:ImportDecoderManifest' :: Text
name = Text
pName_,
      $sel:networkFileDefinitions:ImportDecoderManifest' :: [NetworkFileDefinition]
networkFileDefinitions = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of the decoder manifest to import.
importDecoderManifest_name :: Lens.Lens' ImportDecoderManifest Prelude.Text
importDecoderManifest_name :: Lens' ImportDecoderManifest Text
importDecoderManifest_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportDecoderManifest' {Text
name :: Text
$sel:name:ImportDecoderManifest' :: ImportDecoderManifest -> Text
name} -> Text
name) (\s :: ImportDecoderManifest
s@ImportDecoderManifest' {} Text
a -> ImportDecoderManifest
s {$sel:name:ImportDecoderManifest' :: Text
name = Text
a} :: ImportDecoderManifest)

-- | The file to load into an Amazon Web Services account.
importDecoderManifest_networkFileDefinitions :: Lens.Lens' ImportDecoderManifest [NetworkFileDefinition]
importDecoderManifest_networkFileDefinitions :: Lens' ImportDecoderManifest [NetworkFileDefinition]
importDecoderManifest_networkFileDefinitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportDecoderManifest' {[NetworkFileDefinition]
networkFileDefinitions :: [NetworkFileDefinition]
$sel:networkFileDefinitions:ImportDecoderManifest' :: ImportDecoderManifest -> [NetworkFileDefinition]
networkFileDefinitions} -> [NetworkFileDefinition]
networkFileDefinitions) (\s :: ImportDecoderManifest
s@ImportDecoderManifest' {} [NetworkFileDefinition]
a -> ImportDecoderManifest
s {$sel:networkFileDefinitions:ImportDecoderManifest' :: [NetworkFileDefinition]
networkFileDefinitions = [NetworkFileDefinition]
a} :: ImportDecoderManifest) 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 ImportDecoderManifest where
  type
    AWSResponse ImportDecoderManifest =
      ImportDecoderManifestResponse
  request :: (Service -> Service)
-> ImportDecoderManifest -> Request ImportDecoderManifest
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 ImportDecoderManifest
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ImportDecoderManifest)))
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 -> Text -> ImportDecoderManifestResponse
ImportDecoderManifestResponse'
            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
"name")
            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
"arn")
      )

instance Prelude.Hashable ImportDecoderManifest where
  hashWithSalt :: Int -> ImportDecoderManifest -> Int
hashWithSalt Int
_salt ImportDecoderManifest' {[NetworkFileDefinition]
Text
networkFileDefinitions :: [NetworkFileDefinition]
name :: Text
$sel:networkFileDefinitions:ImportDecoderManifest' :: ImportDecoderManifest -> [NetworkFileDefinition]
$sel:name:ImportDecoderManifest' :: ImportDecoderManifest -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [NetworkFileDefinition]
networkFileDefinitions

instance Prelude.NFData ImportDecoderManifest where
  rnf :: ImportDecoderManifest -> ()
rnf ImportDecoderManifest' {[NetworkFileDefinition]
Text
networkFileDefinitions :: [NetworkFileDefinition]
name :: Text
$sel:networkFileDefinitions:ImportDecoderManifest' :: ImportDecoderManifest -> [NetworkFileDefinition]
$sel:name:ImportDecoderManifest' :: ImportDecoderManifest -> Text
..} =
    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 [NetworkFileDefinition]
networkFileDefinitions

instance Data.ToHeaders ImportDecoderManifest where
  toHeaders :: ImportDecoderManifest -> 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
"IoTAutobahnControlPlane.ImportDecoderManifest" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ImportDecoderManifest where
  toJSON :: ImportDecoderManifest -> Value
toJSON ImportDecoderManifest' {[NetworkFileDefinition]
Text
networkFileDefinitions :: [NetworkFileDefinition]
name :: Text
$sel:networkFileDefinitions:ImportDecoderManifest' :: ImportDecoderManifest -> [NetworkFileDefinition]
$sel:name:ImportDecoderManifest' :: ImportDecoderManifest -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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
"networkFileDefinitions"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [NetworkFileDefinition]
networkFileDefinitions
              )
          ]
      )

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

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

-- | /See:/ 'newImportDecoderManifestResponse' smart constructor.
data ImportDecoderManifestResponse = ImportDecoderManifestResponse'
  { -- | The response's http status code.
    ImportDecoderManifestResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the imported decoder manifest.
    ImportDecoderManifestResponse -> Text
name :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the decoder manifest that was
    -- imported.
    ImportDecoderManifestResponse -> Text
arn :: Prelude.Text
  }
  deriving (ImportDecoderManifestResponse
-> ImportDecoderManifestResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportDecoderManifestResponse
-> ImportDecoderManifestResponse -> Bool
$c/= :: ImportDecoderManifestResponse
-> ImportDecoderManifestResponse -> Bool
== :: ImportDecoderManifestResponse
-> ImportDecoderManifestResponse -> Bool
$c== :: ImportDecoderManifestResponse
-> ImportDecoderManifestResponse -> Bool
Prelude.Eq, ReadPrec [ImportDecoderManifestResponse]
ReadPrec ImportDecoderManifestResponse
Int -> ReadS ImportDecoderManifestResponse
ReadS [ImportDecoderManifestResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportDecoderManifestResponse]
$creadListPrec :: ReadPrec [ImportDecoderManifestResponse]
readPrec :: ReadPrec ImportDecoderManifestResponse
$creadPrec :: ReadPrec ImportDecoderManifestResponse
readList :: ReadS [ImportDecoderManifestResponse]
$creadList :: ReadS [ImportDecoderManifestResponse]
readsPrec :: Int -> ReadS ImportDecoderManifestResponse
$creadsPrec :: Int -> ReadS ImportDecoderManifestResponse
Prelude.Read, Int -> ImportDecoderManifestResponse -> ShowS
[ImportDecoderManifestResponse] -> ShowS
ImportDecoderManifestResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportDecoderManifestResponse] -> ShowS
$cshowList :: [ImportDecoderManifestResponse] -> ShowS
show :: ImportDecoderManifestResponse -> String
$cshow :: ImportDecoderManifestResponse -> String
showsPrec :: Int -> ImportDecoderManifestResponse -> ShowS
$cshowsPrec :: Int -> ImportDecoderManifestResponse -> ShowS
Prelude.Show, forall x.
Rep ImportDecoderManifestResponse x
-> ImportDecoderManifestResponse
forall x.
ImportDecoderManifestResponse
-> Rep ImportDecoderManifestResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ImportDecoderManifestResponse x
-> ImportDecoderManifestResponse
$cfrom :: forall x.
ImportDecoderManifestResponse
-> Rep ImportDecoderManifestResponse x
Prelude.Generic)

-- |
-- Create a value of 'ImportDecoderManifestResponse' 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:
--
-- 'httpStatus', 'importDecoderManifestResponse_httpStatus' - The response's http status code.
--
-- 'name', 'importDecoderManifestResponse_name' - The name of the imported decoder manifest.
--
-- 'arn', 'importDecoderManifestResponse_arn' - The Amazon Resource Name (ARN) of the decoder manifest that was
-- imported.
newImportDecoderManifestResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'name'
  Prelude.Text ->
  -- | 'arn'
  Prelude.Text ->
  ImportDecoderManifestResponse
newImportDecoderManifestResponse :: Int -> Text -> Text -> ImportDecoderManifestResponse
newImportDecoderManifestResponse
  Int
pHttpStatus_
  Text
pName_
  Text
pArn_ =
    ImportDecoderManifestResponse'
      { $sel:httpStatus:ImportDecoderManifestResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:name:ImportDecoderManifestResponse' :: Text
name = Text
pName_,
        $sel:arn:ImportDecoderManifestResponse' :: Text
arn = Text
pArn_
      }

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

-- | The name of the imported decoder manifest.
importDecoderManifestResponse_name :: Lens.Lens' ImportDecoderManifestResponse Prelude.Text
importDecoderManifestResponse_name :: Lens' ImportDecoderManifestResponse Text
importDecoderManifestResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportDecoderManifestResponse' {Text
name :: Text
$sel:name:ImportDecoderManifestResponse' :: ImportDecoderManifestResponse -> Text
name} -> Text
name) (\s :: ImportDecoderManifestResponse
s@ImportDecoderManifestResponse' {} Text
a -> ImportDecoderManifestResponse
s {$sel:name:ImportDecoderManifestResponse' :: Text
name = Text
a} :: ImportDecoderManifestResponse)

-- | The Amazon Resource Name (ARN) of the decoder manifest that was
-- imported.
importDecoderManifestResponse_arn :: Lens.Lens' ImportDecoderManifestResponse Prelude.Text
importDecoderManifestResponse_arn :: Lens' ImportDecoderManifestResponse Text
importDecoderManifestResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportDecoderManifestResponse' {Text
arn :: Text
$sel:arn:ImportDecoderManifestResponse' :: ImportDecoderManifestResponse -> Text
arn} -> Text
arn) (\s :: ImportDecoderManifestResponse
s@ImportDecoderManifestResponse' {} Text
a -> ImportDecoderManifestResponse
s {$sel:arn:ImportDecoderManifestResponse' :: Text
arn = Text
a} :: ImportDecoderManifestResponse)

instance Prelude.NFData ImportDecoderManifestResponse where
  rnf :: ImportDecoderManifestResponse -> ()
rnf ImportDecoderManifestResponse' {Int
Text
arn :: Text
name :: Text
httpStatus :: Int
$sel:arn:ImportDecoderManifestResponse' :: ImportDecoderManifestResponse -> Text
$sel:name:ImportDecoderManifestResponse' :: ImportDecoderManifestResponse -> Text
$sel:httpStatus:ImportDecoderManifestResponse' :: ImportDecoderManifestResponse -> 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
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn