{-# 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.Comprehend.BatchDetectSyntax
(
BatchDetectSyntax (..),
newBatchDetectSyntax,
batchDetectSyntax_textList,
batchDetectSyntax_languageCode,
BatchDetectSyntaxResponse (..),
newBatchDetectSyntaxResponse,
batchDetectSyntaxResponse_httpStatus,
batchDetectSyntaxResponse_resultList,
batchDetectSyntaxResponse_errorList,
)
where
import Amazonka.Comprehend.Types
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
data BatchDetectSyntax = BatchDetectSyntax'
{
BatchDetectSyntax -> Sensitive (NonEmpty (Sensitive Text))
textList :: Data.Sensitive (Prelude.NonEmpty (Data.Sensitive Prelude.Text)),
BatchDetectSyntax -> SyntaxLanguageCode
languageCode :: SyntaxLanguageCode
}
deriving (BatchDetectSyntax -> BatchDetectSyntax -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDetectSyntax -> BatchDetectSyntax -> Bool
$c/= :: BatchDetectSyntax -> BatchDetectSyntax -> Bool
== :: BatchDetectSyntax -> BatchDetectSyntax -> Bool
$c== :: BatchDetectSyntax -> BatchDetectSyntax -> Bool
Prelude.Eq, Int -> BatchDetectSyntax -> ShowS
[BatchDetectSyntax] -> ShowS
BatchDetectSyntax -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDetectSyntax] -> ShowS
$cshowList :: [BatchDetectSyntax] -> ShowS
show :: BatchDetectSyntax -> String
$cshow :: BatchDetectSyntax -> String
showsPrec :: Int -> BatchDetectSyntax -> ShowS
$cshowsPrec :: Int -> BatchDetectSyntax -> ShowS
Prelude.Show, forall x. Rep BatchDetectSyntax x -> BatchDetectSyntax
forall x. BatchDetectSyntax -> Rep BatchDetectSyntax x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchDetectSyntax x -> BatchDetectSyntax
$cfrom :: forall x. BatchDetectSyntax -> Rep BatchDetectSyntax x
Prelude.Generic)
newBatchDetectSyntax ::
Prelude.NonEmpty Prelude.Text ->
SyntaxLanguageCode ->
BatchDetectSyntax
newBatchDetectSyntax :: NonEmpty Text -> SyntaxLanguageCode -> BatchDetectSyntax
newBatchDetectSyntax NonEmpty Text
pTextList_ SyntaxLanguageCode
pLanguageCode_ =
BatchDetectSyntax'
{ $sel:textList:BatchDetectSyntax' :: Sensitive (NonEmpty (Sensitive Text))
textList =
forall a. Iso' (Sensitive a) a
Data._Sensitive
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
forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pTextList_,
$sel:languageCode:BatchDetectSyntax' :: SyntaxLanguageCode
languageCode = SyntaxLanguageCode
pLanguageCode_
}
batchDetectSyntax_textList :: Lens.Lens' BatchDetectSyntax (Prelude.NonEmpty Prelude.Text)
batchDetectSyntax_textList :: Lens' BatchDetectSyntax (NonEmpty Text)
batchDetectSyntax_textList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectSyntax' {Sensitive (NonEmpty (Sensitive Text))
textList :: Sensitive (NonEmpty (Sensitive Text))
$sel:textList:BatchDetectSyntax' :: BatchDetectSyntax -> Sensitive (NonEmpty (Sensitive Text))
textList} -> Sensitive (NonEmpty (Sensitive Text))
textList) (\s :: BatchDetectSyntax
s@BatchDetectSyntax' {} Sensitive (NonEmpty (Sensitive Text))
a -> BatchDetectSyntax
s {$sel:textList:BatchDetectSyntax' :: Sensitive (NonEmpty (Sensitive Text))
textList = Sensitive (NonEmpty (Sensitive Text))
a} :: BatchDetectSyntax) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive 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
batchDetectSyntax_languageCode :: Lens.Lens' BatchDetectSyntax SyntaxLanguageCode
batchDetectSyntax_languageCode :: Lens' BatchDetectSyntax SyntaxLanguageCode
batchDetectSyntax_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectSyntax' {SyntaxLanguageCode
languageCode :: SyntaxLanguageCode
$sel:languageCode:BatchDetectSyntax' :: BatchDetectSyntax -> SyntaxLanguageCode
languageCode} -> SyntaxLanguageCode
languageCode) (\s :: BatchDetectSyntax
s@BatchDetectSyntax' {} SyntaxLanguageCode
a -> BatchDetectSyntax
s {$sel:languageCode:BatchDetectSyntax' :: SyntaxLanguageCode
languageCode = SyntaxLanguageCode
a} :: BatchDetectSyntax)
instance Core.AWSRequest BatchDetectSyntax where
type
AWSResponse BatchDetectSyntax =
BatchDetectSyntaxResponse
request :: (Service -> Service)
-> BatchDetectSyntax -> Request BatchDetectSyntax
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 BatchDetectSyntax
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse BatchDetectSyntax)))
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
-> [BatchDetectSyntaxItemResult]
-> [BatchItemError]
-> BatchDetectSyntaxResponse
BatchDetectSyntaxResponse'
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 (Maybe a)
Data..?> Key
"ResultList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
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
"ErrorList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
)
instance Prelude.Hashable BatchDetectSyntax where
hashWithSalt :: Int -> BatchDetectSyntax -> Int
hashWithSalt Int
_salt BatchDetectSyntax' {Sensitive (NonEmpty (Sensitive Text))
SyntaxLanguageCode
languageCode :: SyntaxLanguageCode
textList :: Sensitive (NonEmpty (Sensitive Text))
$sel:languageCode:BatchDetectSyntax' :: BatchDetectSyntax -> SyntaxLanguageCode
$sel:textList:BatchDetectSyntax' :: BatchDetectSyntax -> Sensitive (NonEmpty (Sensitive Text))
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive (NonEmpty (Sensitive Text))
textList
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SyntaxLanguageCode
languageCode
instance Prelude.NFData BatchDetectSyntax where
rnf :: BatchDetectSyntax -> ()
rnf BatchDetectSyntax' {Sensitive (NonEmpty (Sensitive Text))
SyntaxLanguageCode
languageCode :: SyntaxLanguageCode
textList :: Sensitive (NonEmpty (Sensitive Text))
$sel:languageCode:BatchDetectSyntax' :: BatchDetectSyntax -> SyntaxLanguageCode
$sel:textList:BatchDetectSyntax' :: BatchDetectSyntax -> Sensitive (NonEmpty (Sensitive Text))
..} =
forall a. NFData a => a -> ()
Prelude.rnf Sensitive (NonEmpty (Sensitive Text))
textList
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SyntaxLanguageCode
languageCode
instance Data.ToHeaders BatchDetectSyntax where
toHeaders :: BatchDetectSyntax -> 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
"Comprehend_20171127.BatchDetectSyntax" ::
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 BatchDetectSyntax where
toJSON :: BatchDetectSyntax -> Value
toJSON BatchDetectSyntax' {Sensitive (NonEmpty (Sensitive Text))
SyntaxLanguageCode
languageCode :: SyntaxLanguageCode
textList :: Sensitive (NonEmpty (Sensitive Text))
$sel:languageCode:BatchDetectSyntax' :: BatchDetectSyntax -> SyntaxLanguageCode
$sel:textList:BatchDetectSyntax' :: BatchDetectSyntax -> Sensitive (NonEmpty (Sensitive Text))
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ forall a. a -> Maybe a
Prelude.Just (Key
"TextList" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive (NonEmpty (Sensitive Text))
textList),
forall a. a -> Maybe a
Prelude.Just (Key
"LanguageCode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= SyntaxLanguageCode
languageCode)
]
)
instance Data.ToPath BatchDetectSyntax where
toPath :: BatchDetectSyntax -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery BatchDetectSyntax where
toQuery :: BatchDetectSyntax -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data BatchDetectSyntaxResponse = BatchDetectSyntaxResponse'
{
BatchDetectSyntaxResponse -> Int
httpStatus :: Prelude.Int,
BatchDetectSyntaxResponse -> [BatchDetectSyntaxItemResult]
resultList :: [BatchDetectSyntaxItemResult],
BatchDetectSyntaxResponse -> [BatchItemError]
errorList :: [BatchItemError]
}
deriving (BatchDetectSyntaxResponse -> BatchDetectSyntaxResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDetectSyntaxResponse -> BatchDetectSyntaxResponse -> Bool
$c/= :: BatchDetectSyntaxResponse -> BatchDetectSyntaxResponse -> Bool
== :: BatchDetectSyntaxResponse -> BatchDetectSyntaxResponse -> Bool
$c== :: BatchDetectSyntaxResponse -> BatchDetectSyntaxResponse -> Bool
Prelude.Eq, Int -> BatchDetectSyntaxResponse -> ShowS
[BatchDetectSyntaxResponse] -> ShowS
BatchDetectSyntaxResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDetectSyntaxResponse] -> ShowS
$cshowList :: [BatchDetectSyntaxResponse] -> ShowS
show :: BatchDetectSyntaxResponse -> String
$cshow :: BatchDetectSyntaxResponse -> String
showsPrec :: Int -> BatchDetectSyntaxResponse -> ShowS
$cshowsPrec :: Int -> BatchDetectSyntaxResponse -> ShowS
Prelude.Show, forall x.
Rep BatchDetectSyntaxResponse x -> BatchDetectSyntaxResponse
forall x.
BatchDetectSyntaxResponse -> Rep BatchDetectSyntaxResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDetectSyntaxResponse x -> BatchDetectSyntaxResponse
$cfrom :: forall x.
BatchDetectSyntaxResponse -> Rep BatchDetectSyntaxResponse x
Prelude.Generic)
newBatchDetectSyntaxResponse ::
Prelude.Int ->
BatchDetectSyntaxResponse
newBatchDetectSyntaxResponse :: Int -> BatchDetectSyntaxResponse
newBatchDetectSyntaxResponse Int
pHttpStatus_ =
BatchDetectSyntaxResponse'
{ $sel:httpStatus:BatchDetectSyntaxResponse' :: Int
httpStatus =
Int
pHttpStatus_,
$sel:resultList:BatchDetectSyntaxResponse' :: [BatchDetectSyntaxItemResult]
resultList = forall a. Monoid a => a
Prelude.mempty,
$sel:errorList:BatchDetectSyntaxResponse' :: [BatchItemError]
errorList = forall a. Monoid a => a
Prelude.mempty
}
batchDetectSyntaxResponse_httpStatus :: Lens.Lens' BatchDetectSyntaxResponse Prelude.Int
batchDetectSyntaxResponse_httpStatus :: Lens' BatchDetectSyntaxResponse Int
batchDetectSyntaxResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectSyntaxResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchDetectSyntaxResponse' :: BatchDetectSyntaxResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchDetectSyntaxResponse
s@BatchDetectSyntaxResponse' {} Int
a -> BatchDetectSyntaxResponse
s {$sel:httpStatus:BatchDetectSyntaxResponse' :: Int
httpStatus = Int
a} :: BatchDetectSyntaxResponse)
batchDetectSyntaxResponse_resultList :: Lens.Lens' BatchDetectSyntaxResponse [BatchDetectSyntaxItemResult]
batchDetectSyntaxResponse_resultList :: Lens' BatchDetectSyntaxResponse [BatchDetectSyntaxItemResult]
batchDetectSyntaxResponse_resultList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectSyntaxResponse' {[BatchDetectSyntaxItemResult]
resultList :: [BatchDetectSyntaxItemResult]
$sel:resultList:BatchDetectSyntaxResponse' :: BatchDetectSyntaxResponse -> [BatchDetectSyntaxItemResult]
resultList} -> [BatchDetectSyntaxItemResult]
resultList) (\s :: BatchDetectSyntaxResponse
s@BatchDetectSyntaxResponse' {} [BatchDetectSyntaxItemResult]
a -> BatchDetectSyntaxResponse
s {$sel:resultList:BatchDetectSyntaxResponse' :: [BatchDetectSyntaxItemResult]
resultList = [BatchDetectSyntaxItemResult]
a} :: BatchDetectSyntaxResponse) 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
batchDetectSyntaxResponse_errorList :: Lens.Lens' BatchDetectSyntaxResponse [BatchItemError]
batchDetectSyntaxResponse_errorList :: Lens' BatchDetectSyntaxResponse [BatchItemError]
batchDetectSyntaxResponse_errorList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDetectSyntaxResponse' {[BatchItemError]
errorList :: [BatchItemError]
$sel:errorList:BatchDetectSyntaxResponse' :: BatchDetectSyntaxResponse -> [BatchItemError]
errorList} -> [BatchItemError]
errorList) (\s :: BatchDetectSyntaxResponse
s@BatchDetectSyntaxResponse' {} [BatchItemError]
a -> BatchDetectSyntaxResponse
s {$sel:errorList:BatchDetectSyntaxResponse' :: [BatchItemError]
errorList = [BatchItemError]
a} :: BatchDetectSyntaxResponse) 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 Prelude.NFData BatchDetectSyntaxResponse where
rnf :: BatchDetectSyntaxResponse -> ()
rnf BatchDetectSyntaxResponse' {Int
[BatchItemError]
[BatchDetectSyntaxItemResult]
errorList :: [BatchItemError]
resultList :: [BatchDetectSyntaxItemResult]
httpStatus :: Int
$sel:errorList:BatchDetectSyntaxResponse' :: BatchDetectSyntaxResponse -> [BatchItemError]
$sel:resultList:BatchDetectSyntaxResponse' :: BatchDetectSyntaxResponse -> [BatchDetectSyntaxItemResult]
$sel:httpStatus:BatchDetectSyntaxResponse' :: BatchDetectSyntaxResponse -> 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 [BatchDetectSyntaxItemResult]
resultList
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [BatchItemError]
errorList