{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE MultiWayIf #-}
-- CHANGE WITH CAUTION: This is a generated code file generated by https://github.com/Haskell-OpenAPI-Code-Generator/Haskell-OpenAPI-Client-Code-Generator.
{-# LANGUAGE OverloadedStrings #-}

-- | Contains the different functions to run the operation getIssuingTransactions
module StripeAPI.Operations.GetIssuingTransactions where

import qualified Control.Monad.Fail
import qualified Control.Monad.Trans.Reader
import qualified Data.Aeson
import qualified Data.Aeson as Data.Aeson.Encoding.Internal
import qualified Data.Aeson as Data.Aeson.Types
import qualified Data.Aeson as Data.Aeson.Types.FromJSON
import qualified Data.Aeson as Data.Aeson.Types.Internal
import qualified Data.Aeson as Data.Aeson.Types.ToJSON
import qualified Data.ByteString.Char8
import qualified Data.ByteString.Char8 as Data.ByteString.Internal
import qualified Data.Either
import qualified Data.Functor
import qualified Data.Scientific
import qualified Data.Text
import qualified Data.Text.Internal
import qualified Data.Time.Calendar as Data.Time.Calendar.Days
import qualified Data.Time.LocalTime as Data.Time.LocalTime.Internal.ZonedTime
import qualified Data.Vector
import qualified GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified Network.HTTP.Client
import qualified Network.HTTP.Client as Network.HTTP.Client.Request
import qualified Network.HTTP.Client as Network.HTTP.Client.Types
import qualified Network.HTTP.Simple
import qualified Network.HTTP.Types
import qualified Network.HTTP.Types as Network.HTTP.Types.Status
import qualified Network.HTTP.Types as Network.HTTP.Types.URI
import qualified StripeAPI.Common
import StripeAPI.Types
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | > GET /v1/issuing/transactions
--
-- \<p>Returns a list of Issuing \<code>Transaction\<\/code> objects. The objects are sorted in descending order by creation date, with the most recently created object appearing first.\<\/p>
getIssuingTransactions ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | Contains all available parameters of this operation (query and path parameters)
  GetIssuingTransactionsParameters ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.StripeT m (Network.HTTP.Client.Types.Response GetIssuingTransactionsResponse)
getIssuingTransactions :: GetIssuingTransactionsParameters
-> StripeT m (Response GetIssuingTransactionsResponse)
getIssuingTransactions GetIssuingTransactionsParameters
parameters =
  (Response ByteString -> Response GetIssuingTransactionsResponse)
-> StripeT m (Response ByteString)
-> StripeT m (Response GetIssuingTransactionsResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
    ( \Response ByteString
response_0 ->
        (ByteString -> GetIssuingTransactionsResponse)
-> Response ByteString -> Response GetIssuingTransactionsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
          ( (String -> GetIssuingTransactionsResponse)
-> (GetIssuingTransactionsResponse
    -> GetIssuingTransactionsResponse)
-> Either String GetIssuingTransactionsResponse
-> GetIssuingTransactionsResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> GetIssuingTransactionsResponse
GetIssuingTransactionsResponseError GetIssuingTransactionsResponse -> GetIssuingTransactionsResponse
forall a. a -> a
GHC.Base.id
              (Either String GetIssuingTransactionsResponse
 -> GetIssuingTransactionsResponse)
-> (ByteString -> Either String GetIssuingTransactionsResponse)
-> ByteString
-> GetIssuingTransactionsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. ( \Response ByteString
response ByteString
body ->
                             if
                                 | (\Status
status_1 -> Status -> Int
Network.HTTP.Types.Status.statusCode Status
status_1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Int
200) (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                   GetIssuingTransactionsResponseBody200
-> GetIssuingTransactionsResponse
GetIssuingTransactionsResponse200
                                     (GetIssuingTransactionsResponseBody200
 -> GetIssuingTransactionsResponse)
-> Either String GetIssuingTransactionsResponseBody200
-> Either String GetIssuingTransactionsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String GetIssuingTransactionsResponseBody200
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            GetIssuingTransactionsResponseBody200
                                                      )
                                 | Bool -> Status -> Bool
forall a b. a -> b -> a
GHC.Base.const Bool
GHC.Types.True (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                   Error -> GetIssuingTransactionsResponse
GetIssuingTransactionsResponseDefault
                                     (Error -> GetIssuingTransactionsResponse)
-> Either String Error
-> Either String GetIssuingTransactionsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Error
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            Error
                                                      )
                                 | Bool
GHC.Base.otherwise -> String -> Either String GetIssuingTransactionsResponse
forall a b. a -> Either a b
Data.Either.Left String
"Missing default response type"
                         )
                Response ByteString
response_0
          )
          Response ByteString
response_0
    )
    ( Text -> Text -> [QueryParameter] -> StripeT m (Response ByteString)
forall (m :: * -> *).
MonadHTTP m =>
Text -> Text -> [QueryParameter] -> StripeT m (Response ByteString)
StripeAPI.Common.doCallWithConfigurationM
        (Text -> Text
Data.Text.toUpper (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
GHC.Base.$ String -> Text
Data.Text.pack String
"GET")
        (String -> Text
Data.Text.pack String
"/v1/issuing/transactions")
        [ Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"card") (Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (Text -> Value) -> Maybe Text -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryCard GetIssuingTransactionsParameters
parameters) (String -> Text
Data.Text.pack String
"form") Bool
GHC.Types.True,
          Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"cardholder") (Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (Text -> Value) -> Maybe Text -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryCardholder GetIssuingTransactionsParameters
parameters) (String -> Text
Data.Text.pack String
"form") Bool
GHC.Types.True,
          Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"created") (GetIssuingTransactionsParametersQueryCreated'Variants -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (GetIssuingTransactionsParametersQueryCreated'Variants -> Value)
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
-> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetIssuingTransactionsParameters
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
getIssuingTransactionsParametersQueryCreated GetIssuingTransactionsParameters
parameters) (String -> Text
Data.Text.pack String
"deepObject") Bool
GHC.Types.True,
          Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"ending_before") (Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (Text -> Value) -> Maybe Text -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryEndingBefore GetIssuingTransactionsParameters
parameters) (String -> Text
Data.Text.pack String
"form") Bool
GHC.Types.True,
          Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"expand") ([Text] -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON ([Text] -> Value) -> Maybe [Text] -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetIssuingTransactionsParameters -> Maybe [Text]
getIssuingTransactionsParametersQueryExpand GetIssuingTransactionsParameters
parameters) (String -> Text
Data.Text.pack String
"deepObject") Bool
GHC.Types.True,
          Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"limit") (Int -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (Int -> Value) -> Maybe Int -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetIssuingTransactionsParameters -> Maybe Int
getIssuingTransactionsParametersQueryLimit GetIssuingTransactionsParameters
parameters) (String -> Text
Data.Text.pack String
"form") Bool
GHC.Types.True,
          Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"starting_after") (Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (Text -> Value) -> Maybe Text -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryStartingAfter GetIssuingTransactionsParameters
parameters) (String -> Text
Data.Text.pack String
"form") Bool
GHC.Types.True,
          Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"type") (GetIssuingTransactionsParametersQueryType' -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (GetIssuingTransactionsParametersQueryType' -> Value)
-> Maybe GetIssuingTransactionsParametersQueryType' -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetIssuingTransactionsParameters
-> Maybe GetIssuingTransactionsParametersQueryType'
getIssuingTransactionsParametersQueryType GetIssuingTransactionsParameters
parameters) (String -> Text
Data.Text.pack String
"form") Bool
GHC.Types.True
        ]
    )

-- | Defines the object schema located at @paths.\/v1\/issuing\/transactions.GET.parameters@ in the specification.
data GetIssuingTransactionsParameters = GetIssuingTransactionsParameters
  { -- | queryCard: Represents the parameter named \'card\'
    --
    -- Only return transactions that belong to the given card.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryCard :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | queryCardholder: Represents the parameter named \'cardholder\'
    --
    -- Only return transactions that belong to the given cardholder.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryCardholder :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | queryCreated: Represents the parameter named \'created\'
    --
    -- Only return transactions that were created during the given date interval.
    GetIssuingTransactionsParameters
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
getIssuingTransactionsParametersQueryCreated :: (GHC.Maybe.Maybe GetIssuingTransactionsParametersQueryCreated'Variants),
    -- | queryEnding_before: Represents the parameter named \'ending_before\'
    --
    -- A cursor for use in pagination. \`ending_before\` is an object ID that defines your place in the list. For instance, if you make a list request and receive 100 objects, starting with \`obj_bar\`, your subsequent call can include \`ending_before=obj_bar\` in order to fetch the previous page of the list.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryEndingBefore :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | queryExpand: Represents the parameter named \'expand\'
    --
    -- Specifies which fields in the response should be expanded.
    GetIssuingTransactionsParameters -> Maybe [Text]
getIssuingTransactionsParametersQueryExpand :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | queryLimit: Represents the parameter named \'limit\'
    --
    -- A limit on the number of objects to be returned. Limit can range between 1 and 100, and the default is 10.
    GetIssuingTransactionsParameters -> Maybe Int
getIssuingTransactionsParametersQueryLimit :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | queryStarting_after: Represents the parameter named \'starting_after\'
    --
    -- A cursor for use in pagination. \`starting_after\` is an object ID that defines your place in the list. For instance, if you make a list request and receive 100 objects, ending with \`obj_foo\`, your subsequent call can include \`starting_after=obj_foo\` in order to fetch the next page of the list.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryStartingAfter :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | queryType: Represents the parameter named \'type\'
    --
    -- Only return transactions that have the given type. One of \`capture\` or \`refund\`.
    GetIssuingTransactionsParameters
-> Maybe GetIssuingTransactionsParametersQueryType'
getIssuingTransactionsParametersQueryType :: (GHC.Maybe.Maybe GetIssuingTransactionsParametersQueryType')
  }
  deriving
    ( Int -> GetIssuingTransactionsParameters -> ShowS
[GetIssuingTransactionsParameters] -> ShowS
GetIssuingTransactionsParameters -> String
(Int -> GetIssuingTransactionsParameters -> ShowS)
-> (GetIssuingTransactionsParameters -> String)
-> ([GetIssuingTransactionsParameters] -> ShowS)
-> Show GetIssuingTransactionsParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIssuingTransactionsParameters] -> ShowS
$cshowList :: [GetIssuingTransactionsParameters] -> ShowS
show :: GetIssuingTransactionsParameters -> String
$cshow :: GetIssuingTransactionsParameters -> String
showsPrec :: Int -> GetIssuingTransactionsParameters -> ShowS
$cshowsPrec :: Int -> GetIssuingTransactionsParameters -> ShowS
GHC.Show.Show,
      GetIssuingTransactionsParameters
-> GetIssuingTransactionsParameters -> Bool
(GetIssuingTransactionsParameters
 -> GetIssuingTransactionsParameters -> Bool)
-> (GetIssuingTransactionsParameters
    -> GetIssuingTransactionsParameters -> Bool)
-> Eq GetIssuingTransactionsParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIssuingTransactionsParameters
-> GetIssuingTransactionsParameters -> Bool
$c/= :: GetIssuingTransactionsParameters
-> GetIssuingTransactionsParameters -> Bool
== :: GetIssuingTransactionsParameters
-> GetIssuingTransactionsParameters -> Bool
$c== :: GetIssuingTransactionsParameters
-> GetIssuingTransactionsParameters -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON GetIssuingTransactionsParameters where
  toJSON :: GetIssuingTransactionsParameters -> Value
toJSON GetIssuingTransactionsParameters
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"queryCard" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryCard GetIssuingTransactionsParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryCardholder" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryCardholder GetIssuingTransactionsParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryCreated" Text
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
getIssuingTransactionsParametersQueryCreated GetIssuingTransactionsParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryEnding_before" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryEndingBefore GetIssuingTransactionsParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryExpand" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe [Text]
getIssuingTransactionsParametersQueryExpand GetIssuingTransactionsParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryLimit" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Int
getIssuingTransactionsParametersQueryLimit GetIssuingTransactionsParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryStarting_after" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryStartingAfter GetIssuingTransactionsParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryType" Text -> Maybe GetIssuingTransactionsParametersQueryType' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters
-> Maybe GetIssuingTransactionsParametersQueryType'
getIssuingTransactionsParametersQueryType GetIssuingTransactionsParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: GetIssuingTransactionsParameters -> Encoding
toEncoding GetIssuingTransactionsParameters
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"queryCard" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryCard GetIssuingTransactionsParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryCardholder" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryCardholder GetIssuingTransactionsParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryCreated" Text
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
getIssuingTransactionsParametersQueryCreated GetIssuingTransactionsParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryEnding_before" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryEndingBefore GetIssuingTransactionsParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryExpand" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe [Text]
getIssuingTransactionsParametersQueryExpand GetIssuingTransactionsParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryLimit" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Int
getIssuingTransactionsParametersQueryLimit GetIssuingTransactionsParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryStarting_after" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters -> Maybe Text
getIssuingTransactionsParametersQueryStartingAfter GetIssuingTransactionsParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"queryType" Text -> Maybe GetIssuingTransactionsParametersQueryType' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParameters
-> Maybe GetIssuingTransactionsParametersQueryType'
getIssuingTransactionsParametersQueryType GetIssuingTransactionsParameters
obj))))))))

instance Data.Aeson.Types.FromJSON.FromJSON GetIssuingTransactionsParameters where
  parseJSON :: Value -> Parser GetIssuingTransactionsParameters
parseJSON = String
-> (Object -> Parser GetIssuingTransactionsParameters)
-> Value
-> Parser GetIssuingTransactionsParameters
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GetIssuingTransactionsParameters" (\Object
obj -> ((((((((Maybe Text
 -> Maybe Text
 -> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
 -> Maybe Text
 -> Maybe [Text]
 -> Maybe Int
 -> Maybe Text
 -> Maybe GetIssuingTransactionsParametersQueryType'
 -> GetIssuingTransactionsParameters)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryType'
      -> GetIssuingTransactionsParameters)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Text
-> Maybe GetIssuingTransactionsParametersQueryType'
-> GetIssuingTransactionsParameters
GetIssuingTransactionsParameters Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryType'
   -> GetIssuingTransactionsParameters)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryType'
      -> GetIssuingTransactionsParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryCard")) Parser
  (Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryType'
   -> GetIssuingTransactionsParameters)
-> Parser (Maybe Text)
-> Parser
     (Maybe GetIssuingTransactionsParametersQueryCreated'Variants
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryType'
      -> GetIssuingTransactionsParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryCardholder")) Parser
  (Maybe GetIssuingTransactionsParametersQueryCreated'Variants
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryType'
   -> GetIssuingTransactionsParameters)
-> Parser
     (Maybe GetIssuingTransactionsParametersQueryCreated'Variants)
-> Parser
     (Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryType'
      -> GetIssuingTransactionsParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe GetIssuingTransactionsParametersQueryCreated'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryCreated")) Parser
  (Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryType'
   -> GetIssuingTransactionsParameters)
-> Parser (Maybe Text)
-> Parser
     (Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryType'
      -> GetIssuingTransactionsParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryEnding_before")) Parser
  (Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryType'
   -> GetIssuingTransactionsParameters)
-> Parser (Maybe [Text])
-> Parser
     (Maybe Int
      -> Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryType'
      -> GetIssuingTransactionsParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryExpand")) Parser
  (Maybe Int
   -> Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryType'
   -> GetIssuingTransactionsParameters)
-> Parser (Maybe Int)
-> Parser
     (Maybe Text
      -> Maybe GetIssuingTransactionsParametersQueryType'
      -> GetIssuingTransactionsParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryLimit")) Parser
  (Maybe Text
   -> Maybe GetIssuingTransactionsParametersQueryType'
   -> GetIssuingTransactionsParameters)
-> Parser (Maybe Text)
-> Parser
     (Maybe GetIssuingTransactionsParametersQueryType'
      -> GetIssuingTransactionsParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryStarting_after")) Parser
  (Maybe GetIssuingTransactionsParametersQueryType'
   -> GetIssuingTransactionsParameters)
-> Parser (Maybe GetIssuingTransactionsParametersQueryType')
-> Parser GetIssuingTransactionsParameters
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe GetIssuingTransactionsParametersQueryType')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryType"))

-- | Create a new 'GetIssuingTransactionsParameters' with all required fields.
mkGetIssuingTransactionsParameters :: GetIssuingTransactionsParameters
mkGetIssuingTransactionsParameters :: GetIssuingTransactionsParameters
mkGetIssuingTransactionsParameters =
  GetIssuingTransactionsParameters :: Maybe Text
-> Maybe Text
-> Maybe GetIssuingTransactionsParametersQueryCreated'Variants
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Text
-> Maybe GetIssuingTransactionsParametersQueryType'
-> GetIssuingTransactionsParameters
GetIssuingTransactionsParameters
    { getIssuingTransactionsParametersQueryCard :: Maybe Text
getIssuingTransactionsParametersQueryCard = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryCardholder :: Maybe Text
getIssuingTransactionsParametersQueryCardholder = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryCreated :: Maybe GetIssuingTransactionsParametersQueryCreated'Variants
getIssuingTransactionsParametersQueryCreated = Maybe GetIssuingTransactionsParametersQueryCreated'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryEndingBefore :: Maybe Text
getIssuingTransactionsParametersQueryEndingBefore = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryExpand :: Maybe [Text]
getIssuingTransactionsParametersQueryExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryLimit :: Maybe Int
getIssuingTransactionsParametersQueryLimit = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryStartingAfter :: Maybe Text
getIssuingTransactionsParametersQueryStartingAfter = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryType :: Maybe GetIssuingTransactionsParametersQueryType'
getIssuingTransactionsParametersQueryType = Maybe GetIssuingTransactionsParametersQueryType'
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/issuing\/transactions.GET.parameters.properties.queryCreated.anyOf@ in the specification.
data GetIssuingTransactionsParametersQueryCreated'OneOf1 = GetIssuingTransactionsParametersQueryCreated'OneOf1
  { -- | gt
    GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Gt :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | gte
    GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Gte :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | lt
    GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Lt :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | lte
    GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Lte :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int -> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> ShowS
[GetIssuingTransactionsParametersQueryCreated'OneOf1] -> ShowS
GetIssuingTransactionsParametersQueryCreated'OneOf1 -> String
(Int
 -> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> ShowS)
-> (GetIssuingTransactionsParametersQueryCreated'OneOf1 -> String)
-> ([GetIssuingTransactionsParametersQueryCreated'OneOf1] -> ShowS)
-> Show GetIssuingTransactionsParametersQueryCreated'OneOf1
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIssuingTransactionsParametersQueryCreated'OneOf1] -> ShowS
$cshowList :: [GetIssuingTransactionsParametersQueryCreated'OneOf1] -> ShowS
show :: GetIssuingTransactionsParametersQueryCreated'OneOf1 -> String
$cshow :: GetIssuingTransactionsParametersQueryCreated'OneOf1 -> String
showsPrec :: Int -> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> ShowS
$cshowsPrec :: Int -> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> ShowS
GHC.Show.Show,
      GetIssuingTransactionsParametersQueryCreated'OneOf1
-> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Bool
(GetIssuingTransactionsParametersQueryCreated'OneOf1
 -> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Bool)
-> (GetIssuingTransactionsParametersQueryCreated'OneOf1
    -> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Bool)
-> Eq GetIssuingTransactionsParametersQueryCreated'OneOf1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIssuingTransactionsParametersQueryCreated'OneOf1
-> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Bool
$c/= :: GetIssuingTransactionsParametersQueryCreated'OneOf1
-> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Bool
== :: GetIssuingTransactionsParametersQueryCreated'OneOf1
-> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Bool
$c== :: GetIssuingTransactionsParametersQueryCreated'OneOf1
-> GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON GetIssuingTransactionsParametersQueryCreated'OneOf1 where
  toJSON :: GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Value
toJSON GetIssuingTransactionsParametersQueryCreated'OneOf1
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"gt" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Gt GetIssuingTransactionsParametersQueryCreated'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"gte" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Gte GetIssuingTransactionsParametersQueryCreated'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"lt" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Lt GetIssuingTransactionsParametersQueryCreated'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"lte" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Lte GetIssuingTransactionsParametersQueryCreated'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Encoding
toEncoding GetIssuingTransactionsParametersQueryCreated'OneOf1
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"gt" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Gt GetIssuingTransactionsParametersQueryCreated'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"gte" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Gte GetIssuingTransactionsParametersQueryCreated'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"lt" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Lt GetIssuingTransactionsParametersQueryCreated'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"lte" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Lte GetIssuingTransactionsParametersQueryCreated'OneOf1
obj))))

instance Data.Aeson.Types.FromJSON.FromJSON GetIssuingTransactionsParametersQueryCreated'OneOf1 where
  parseJSON :: Value -> Parser GetIssuingTransactionsParametersQueryCreated'OneOf1
parseJSON = String
-> (Object
    -> Parser GetIssuingTransactionsParametersQueryCreated'OneOf1)
-> Value
-> Parser GetIssuingTransactionsParametersQueryCreated'OneOf1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GetIssuingTransactionsParametersQueryCreated'OneOf1" (\Object
obj -> ((((Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> GetIssuingTransactionsParametersQueryCreated'OneOf1
GetIssuingTransactionsParametersQueryCreated'OneOf1 Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"gt")) Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"gte")) Parser
  (Maybe Int
   -> Maybe Int
   -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"lt")) Parser
  (Maybe Int -> GetIssuingTransactionsParametersQueryCreated'OneOf1)
-> Parser (Maybe Int)
-> Parser GetIssuingTransactionsParametersQueryCreated'OneOf1
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"lte"))

-- | Create a new 'GetIssuingTransactionsParametersQueryCreated'OneOf1' with all required fields.
mkGetIssuingTransactionsParametersQueryCreated'OneOf1 :: GetIssuingTransactionsParametersQueryCreated'OneOf1
mkGetIssuingTransactionsParametersQueryCreated'OneOf1 :: GetIssuingTransactionsParametersQueryCreated'OneOf1
mkGetIssuingTransactionsParametersQueryCreated'OneOf1 =
  GetIssuingTransactionsParametersQueryCreated'OneOf1 :: Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> GetIssuingTransactionsParametersQueryCreated'OneOf1
GetIssuingTransactionsParametersQueryCreated'OneOf1
    { getIssuingTransactionsParametersQueryCreated'OneOf1Gt :: Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Gt = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryCreated'OneOf1Gte :: Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Gte = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryCreated'OneOf1Lt :: Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Lt = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      getIssuingTransactionsParametersQueryCreated'OneOf1Lte :: Maybe Int
getIssuingTransactionsParametersQueryCreated'OneOf1Lte = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the oneOf schema located at @paths.\/v1\/issuing\/transactions.GET.parameters.properties.queryCreated.anyOf@ in the specification.
--
-- Represents the parameter named \'created\'
--
-- Only return transactions that were created during the given date interval.
data GetIssuingTransactionsParametersQueryCreated'Variants
  = GetIssuingTransactionsParametersQueryCreated'GetIssuingTransactionsParametersQueryCreated'OneOf1 GetIssuingTransactionsParametersQueryCreated'OneOf1
  | GetIssuingTransactionsParametersQueryCreated'Int GHC.Types.Int
  deriving (Int
-> GetIssuingTransactionsParametersQueryCreated'Variants -> ShowS
[GetIssuingTransactionsParametersQueryCreated'Variants] -> ShowS
GetIssuingTransactionsParametersQueryCreated'Variants -> String
(Int
 -> GetIssuingTransactionsParametersQueryCreated'Variants -> ShowS)
-> (GetIssuingTransactionsParametersQueryCreated'Variants
    -> String)
-> ([GetIssuingTransactionsParametersQueryCreated'Variants]
    -> ShowS)
-> Show GetIssuingTransactionsParametersQueryCreated'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIssuingTransactionsParametersQueryCreated'Variants] -> ShowS
$cshowList :: [GetIssuingTransactionsParametersQueryCreated'Variants] -> ShowS
show :: GetIssuingTransactionsParametersQueryCreated'Variants -> String
$cshow :: GetIssuingTransactionsParametersQueryCreated'Variants -> String
showsPrec :: Int
-> GetIssuingTransactionsParametersQueryCreated'Variants -> ShowS
$cshowsPrec :: Int
-> GetIssuingTransactionsParametersQueryCreated'Variants -> ShowS
GHC.Show.Show, GetIssuingTransactionsParametersQueryCreated'Variants
-> GetIssuingTransactionsParametersQueryCreated'Variants -> Bool
(GetIssuingTransactionsParametersQueryCreated'Variants
 -> GetIssuingTransactionsParametersQueryCreated'Variants -> Bool)
-> (GetIssuingTransactionsParametersQueryCreated'Variants
    -> GetIssuingTransactionsParametersQueryCreated'Variants -> Bool)
-> Eq GetIssuingTransactionsParametersQueryCreated'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIssuingTransactionsParametersQueryCreated'Variants
-> GetIssuingTransactionsParametersQueryCreated'Variants -> Bool
$c/= :: GetIssuingTransactionsParametersQueryCreated'Variants
-> GetIssuingTransactionsParametersQueryCreated'Variants -> Bool
== :: GetIssuingTransactionsParametersQueryCreated'Variants
-> GetIssuingTransactionsParametersQueryCreated'Variants -> Bool
$c== :: GetIssuingTransactionsParametersQueryCreated'Variants
-> GetIssuingTransactionsParametersQueryCreated'Variants -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON GetIssuingTransactionsParametersQueryCreated'Variants where
  toJSON :: GetIssuingTransactionsParametersQueryCreated'Variants -> Value
toJSON (GetIssuingTransactionsParametersQueryCreated'GetIssuingTransactionsParametersQueryCreated'OneOf1 GetIssuingTransactionsParametersQueryCreated'OneOf1
a) = GetIssuingTransactionsParametersQueryCreated'OneOf1 -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON GetIssuingTransactionsParametersQueryCreated'OneOf1
a
  toJSON (GetIssuingTransactionsParametersQueryCreated'Int Int
a) = Int -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Int
a

instance Data.Aeson.Types.FromJSON.FromJSON GetIssuingTransactionsParametersQueryCreated'Variants where
  parseJSON :: Value
-> Parser GetIssuingTransactionsParametersQueryCreated'Variants
parseJSON Value
val = case (GetIssuingTransactionsParametersQueryCreated'OneOf1
-> GetIssuingTransactionsParametersQueryCreated'Variants
GetIssuingTransactionsParametersQueryCreated'GetIssuingTransactionsParametersQueryCreated'OneOf1 (GetIssuingTransactionsParametersQueryCreated'OneOf1
 -> GetIssuingTransactionsParametersQueryCreated'Variants)
-> Result GetIssuingTransactionsParametersQueryCreated'OneOf1
-> Result GetIssuingTransactionsParametersQueryCreated'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result GetIssuingTransactionsParametersQueryCreated'OneOf1
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result GetIssuingTransactionsParametersQueryCreated'Variants
-> Result GetIssuingTransactionsParametersQueryCreated'Variants
-> Result GetIssuingTransactionsParametersQueryCreated'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Int -> GetIssuingTransactionsParametersQueryCreated'Variants
GetIssuingTransactionsParametersQueryCreated'Int (Int -> GetIssuingTransactionsParametersQueryCreated'Variants)
-> Result Int
-> Result GetIssuingTransactionsParametersQueryCreated'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Int
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result GetIssuingTransactionsParametersQueryCreated'Variants
-> Result GetIssuingTransactionsParametersQueryCreated'Variants
-> Result GetIssuingTransactionsParametersQueryCreated'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result GetIssuingTransactionsParametersQueryCreated'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
    Data.Aeson.Types.Internal.Success GetIssuingTransactionsParametersQueryCreated'Variants
a -> GetIssuingTransactionsParametersQueryCreated'Variants
-> Parser GetIssuingTransactionsParametersQueryCreated'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure GetIssuingTransactionsParametersQueryCreated'Variants
a
    Data.Aeson.Types.Internal.Error String
a -> String
-> Parser GetIssuingTransactionsParametersQueryCreated'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a

-- | Defines the enum schema located at @paths.\/v1\/issuing\/transactions.GET.parameters.properties.queryType@ in the specification.
--
-- Represents the parameter named \'type\'
--
-- Only return transactions that have the given type. One of \`capture\` or \`refund\`.
data GetIssuingTransactionsParametersQueryType'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    GetIssuingTransactionsParametersQueryType'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    GetIssuingTransactionsParametersQueryType'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"capture"@
    GetIssuingTransactionsParametersQueryType'EnumCapture
  | -- | Represents the JSON value @"refund"@
    GetIssuingTransactionsParametersQueryType'EnumRefund
  deriving (Int -> GetIssuingTransactionsParametersQueryType' -> ShowS
[GetIssuingTransactionsParametersQueryType'] -> ShowS
GetIssuingTransactionsParametersQueryType' -> String
(Int -> GetIssuingTransactionsParametersQueryType' -> ShowS)
-> (GetIssuingTransactionsParametersQueryType' -> String)
-> ([GetIssuingTransactionsParametersQueryType'] -> ShowS)
-> Show GetIssuingTransactionsParametersQueryType'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIssuingTransactionsParametersQueryType'] -> ShowS
$cshowList :: [GetIssuingTransactionsParametersQueryType'] -> ShowS
show :: GetIssuingTransactionsParametersQueryType' -> String
$cshow :: GetIssuingTransactionsParametersQueryType' -> String
showsPrec :: Int -> GetIssuingTransactionsParametersQueryType' -> ShowS
$cshowsPrec :: Int -> GetIssuingTransactionsParametersQueryType' -> ShowS
GHC.Show.Show, GetIssuingTransactionsParametersQueryType'
-> GetIssuingTransactionsParametersQueryType' -> Bool
(GetIssuingTransactionsParametersQueryType'
 -> GetIssuingTransactionsParametersQueryType' -> Bool)
-> (GetIssuingTransactionsParametersQueryType'
    -> GetIssuingTransactionsParametersQueryType' -> Bool)
-> Eq GetIssuingTransactionsParametersQueryType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIssuingTransactionsParametersQueryType'
-> GetIssuingTransactionsParametersQueryType' -> Bool
$c/= :: GetIssuingTransactionsParametersQueryType'
-> GetIssuingTransactionsParametersQueryType' -> Bool
== :: GetIssuingTransactionsParametersQueryType'
-> GetIssuingTransactionsParametersQueryType' -> Bool
$c== :: GetIssuingTransactionsParametersQueryType'
-> GetIssuingTransactionsParametersQueryType' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON GetIssuingTransactionsParametersQueryType' where
  toJSON :: GetIssuingTransactionsParametersQueryType' -> Value
toJSON (GetIssuingTransactionsParametersQueryType'Other Value
val) = Value
val
  toJSON (GetIssuingTransactionsParametersQueryType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (GetIssuingTransactionsParametersQueryType'
GetIssuingTransactionsParametersQueryType'EnumCapture) = Value
"capture"
  toJSON (GetIssuingTransactionsParametersQueryType'
GetIssuingTransactionsParametersQueryType'EnumRefund) = Value
"refund"

instance Data.Aeson.Types.FromJSON.FromJSON GetIssuingTransactionsParametersQueryType' where
  parseJSON :: Value -> Parser GetIssuingTransactionsParametersQueryType'
parseJSON Value
val =
    GetIssuingTransactionsParametersQueryType'
-> Parser GetIssuingTransactionsParametersQueryType'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"capture" -> GetIssuingTransactionsParametersQueryType'
GetIssuingTransactionsParametersQueryType'EnumCapture
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"refund" -> GetIssuingTransactionsParametersQueryType'
GetIssuingTransactionsParametersQueryType'EnumRefund
            | Bool
GHC.Base.otherwise -> Value -> GetIssuingTransactionsParametersQueryType'
GetIssuingTransactionsParametersQueryType'Other Value
val
      )

-- | Represents a response of the operation 'getIssuingTransactions'.
--
-- The response constructor is chosen by the status code of the response. If no case matches (no specific case for the response code, no range case, no default case), 'GetIssuingTransactionsResponseError' is used.
data GetIssuingTransactionsResponse
  = -- | Means either no matching case available or a parse error
    GetIssuingTransactionsResponseError GHC.Base.String
  | -- | Successful response.
    GetIssuingTransactionsResponse200 GetIssuingTransactionsResponseBody200
  | -- | Error response.
    GetIssuingTransactionsResponseDefault Error
  deriving (Int -> GetIssuingTransactionsResponse -> ShowS
[GetIssuingTransactionsResponse] -> ShowS
GetIssuingTransactionsResponse -> String
(Int -> GetIssuingTransactionsResponse -> ShowS)
-> (GetIssuingTransactionsResponse -> String)
-> ([GetIssuingTransactionsResponse] -> ShowS)
-> Show GetIssuingTransactionsResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIssuingTransactionsResponse] -> ShowS
$cshowList :: [GetIssuingTransactionsResponse] -> ShowS
show :: GetIssuingTransactionsResponse -> String
$cshow :: GetIssuingTransactionsResponse -> String
showsPrec :: Int -> GetIssuingTransactionsResponse -> ShowS
$cshowsPrec :: Int -> GetIssuingTransactionsResponse -> ShowS
GHC.Show.Show, GetIssuingTransactionsResponse
-> GetIssuingTransactionsResponse -> Bool
(GetIssuingTransactionsResponse
 -> GetIssuingTransactionsResponse -> Bool)
-> (GetIssuingTransactionsResponse
    -> GetIssuingTransactionsResponse -> Bool)
-> Eq GetIssuingTransactionsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIssuingTransactionsResponse
-> GetIssuingTransactionsResponse -> Bool
$c/= :: GetIssuingTransactionsResponse
-> GetIssuingTransactionsResponse -> Bool
== :: GetIssuingTransactionsResponse
-> GetIssuingTransactionsResponse -> Bool
$c== :: GetIssuingTransactionsResponse
-> GetIssuingTransactionsResponse -> Bool
GHC.Classes.Eq)

-- | Defines the object schema located at @paths.\/v1\/issuing\/transactions.GET.responses.200.content.application\/json.schema@ in the specification.
data GetIssuingTransactionsResponseBody200 = GetIssuingTransactionsResponseBody200
  { -- | data
    GetIssuingTransactionsResponseBody200 -> [Issuing'transaction]
getIssuingTransactionsResponseBody200Data :: ([Issuing'transaction]),
    -- | has_more: True if this list has another page of items after this one that can be fetched.
    GetIssuingTransactionsResponseBody200 -> Bool
getIssuingTransactionsResponseBody200HasMore :: GHC.Types.Bool,
    -- | url: The URL where this list can be accessed.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    -- * Must match pattern \'^\/v1\/issuing\/transactions\'
    GetIssuingTransactionsResponseBody200 -> Text
getIssuingTransactionsResponseBody200Url :: Data.Text.Internal.Text
  }
  deriving
    ( Int -> GetIssuingTransactionsResponseBody200 -> ShowS
[GetIssuingTransactionsResponseBody200] -> ShowS
GetIssuingTransactionsResponseBody200 -> String
(Int -> GetIssuingTransactionsResponseBody200 -> ShowS)
-> (GetIssuingTransactionsResponseBody200 -> String)
-> ([GetIssuingTransactionsResponseBody200] -> ShowS)
-> Show GetIssuingTransactionsResponseBody200
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIssuingTransactionsResponseBody200] -> ShowS
$cshowList :: [GetIssuingTransactionsResponseBody200] -> ShowS
show :: GetIssuingTransactionsResponseBody200 -> String
$cshow :: GetIssuingTransactionsResponseBody200 -> String
showsPrec :: Int -> GetIssuingTransactionsResponseBody200 -> ShowS
$cshowsPrec :: Int -> GetIssuingTransactionsResponseBody200 -> ShowS
GHC.Show.Show,
      GetIssuingTransactionsResponseBody200
-> GetIssuingTransactionsResponseBody200 -> Bool
(GetIssuingTransactionsResponseBody200
 -> GetIssuingTransactionsResponseBody200 -> Bool)
-> (GetIssuingTransactionsResponseBody200
    -> GetIssuingTransactionsResponseBody200 -> Bool)
-> Eq GetIssuingTransactionsResponseBody200
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIssuingTransactionsResponseBody200
-> GetIssuingTransactionsResponseBody200 -> Bool
$c/= :: GetIssuingTransactionsResponseBody200
-> GetIssuingTransactionsResponseBody200 -> Bool
== :: GetIssuingTransactionsResponseBody200
-> GetIssuingTransactionsResponseBody200 -> Bool
$c== :: GetIssuingTransactionsResponseBody200
-> GetIssuingTransactionsResponseBody200 -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON GetIssuingTransactionsResponseBody200 where
  toJSON :: GetIssuingTransactionsResponseBody200 -> Value
toJSON GetIssuingTransactionsResponseBody200
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"data" Text -> [Issuing'transaction] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsResponseBody200 -> [Issuing'transaction]
getIssuingTransactionsResponseBody200Data GetIssuingTransactionsResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"has_more" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsResponseBody200 -> Bool
getIssuingTransactionsResponseBody200HasMore GetIssuingTransactionsResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"url" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsResponseBody200 -> Text
getIssuingTransactionsResponseBody200Url GetIssuingTransactionsResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"object" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Text -> Value
Data.Aeson.Types.Internal.String Text
"list" Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: GetIssuingTransactionsResponseBody200 -> Encoding
toEncoding GetIssuingTransactionsResponseBody200
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"data" Text -> [Issuing'transaction] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsResponseBody200 -> [Issuing'transaction]
getIssuingTransactionsResponseBody200Data GetIssuingTransactionsResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"has_more" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsResponseBody200 -> Bool
getIssuingTransactionsResponseBody200HasMore GetIssuingTransactionsResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"url" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetIssuingTransactionsResponseBody200 -> Text
getIssuingTransactionsResponseBody200Url GetIssuingTransactionsResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"object" Text -> Value -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Text -> Value
Data.Aeson.Types.Internal.String Text
"list"))))

instance Data.Aeson.Types.FromJSON.FromJSON GetIssuingTransactionsResponseBody200 where
  parseJSON :: Value -> Parser GetIssuingTransactionsResponseBody200
parseJSON = String
-> (Object -> Parser GetIssuingTransactionsResponseBody200)
-> Value
-> Parser GetIssuingTransactionsResponseBody200
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GetIssuingTransactionsResponseBody200" (\Object
obj -> ((([Issuing'transaction]
 -> Bool -> Text -> GetIssuingTransactionsResponseBody200)
-> Parser
     ([Issuing'transaction]
      -> Bool -> Text -> GetIssuingTransactionsResponseBody200)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure [Issuing'transaction]
-> Bool -> Text -> GetIssuingTransactionsResponseBody200
GetIssuingTransactionsResponseBody200 Parser
  ([Issuing'transaction]
   -> Bool -> Text -> GetIssuingTransactionsResponseBody200)
-> Parser [Issuing'transaction]
-> Parser (Bool -> Text -> GetIssuingTransactionsResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser [Issuing'transaction]
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"data")) Parser (Bool -> Text -> GetIssuingTransactionsResponseBody200)
-> Parser Bool
-> Parser (Text -> GetIssuingTransactionsResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"has_more")) Parser (Text -> GetIssuingTransactionsResponseBody200)
-> Parser Text -> Parser GetIssuingTransactionsResponseBody200
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"url"))

-- | Create a new 'GetIssuingTransactionsResponseBody200' with all required fields.
mkGetIssuingTransactionsResponseBody200 ::
  -- | 'getIssuingTransactionsResponseBody200Data'
  [Issuing'transaction] ->
  -- | 'getIssuingTransactionsResponseBody200HasMore'
  GHC.Types.Bool ->
  -- | 'getIssuingTransactionsResponseBody200Url'
  Data.Text.Internal.Text ->
  GetIssuingTransactionsResponseBody200
mkGetIssuingTransactionsResponseBody200 :: [Issuing'transaction]
-> Bool -> Text -> GetIssuingTransactionsResponseBody200
mkGetIssuingTransactionsResponseBody200 [Issuing'transaction]
getIssuingTransactionsResponseBody200Data Bool
getIssuingTransactionsResponseBody200HasMore Text
getIssuingTransactionsResponseBody200Url =
  GetIssuingTransactionsResponseBody200 :: [Issuing'transaction]
-> Bool -> Text -> GetIssuingTransactionsResponseBody200
GetIssuingTransactionsResponseBody200
    { getIssuingTransactionsResponseBody200Data :: [Issuing'transaction]
getIssuingTransactionsResponseBody200Data = [Issuing'transaction]
getIssuingTransactionsResponseBody200Data,
      getIssuingTransactionsResponseBody200HasMore :: Bool
getIssuingTransactionsResponseBody200HasMore = Bool
getIssuingTransactionsResponseBody200HasMore,
      getIssuingTransactionsResponseBody200Url :: Text
getIssuingTransactionsResponseBody200Url = Text
getIssuingTransactionsResponseBody200Url
    }