{-# 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 getPromotionCodes
module StripeAPI.Operations.GetPromotionCodes 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/promotion_codes
--
-- \<p>Returns a list of your promotion codes.\<\/p>
getPromotionCodes ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | Contains all available parameters of this operation (query and path parameters)
  GetPromotionCodesParameters ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.ClientT m (Network.HTTP.Client.Types.Response GetPromotionCodesResponse)
getPromotionCodes :: GetPromotionCodesParameters
-> ClientT m (Response GetPromotionCodesResponse)
getPromotionCodes GetPromotionCodesParameters
parameters =
  (Response ByteString -> Response GetPromotionCodesResponse)
-> ClientT m (Response ByteString)
-> ClientT m (Response GetPromotionCodesResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
    ( \Response ByteString
response_0 ->
        (ByteString -> GetPromotionCodesResponse)
-> Response ByteString -> Response GetPromotionCodesResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
          ( (String -> GetPromotionCodesResponse)
-> (GetPromotionCodesResponse -> GetPromotionCodesResponse)
-> Either String GetPromotionCodesResponse
-> GetPromotionCodesResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> GetPromotionCodesResponse
GetPromotionCodesResponseError GetPromotionCodesResponse -> GetPromotionCodesResponse
forall a. a -> a
GHC.Base.id
              (Either String GetPromotionCodesResponse
 -> GetPromotionCodesResponse)
-> (ByteString -> Either String GetPromotionCodesResponse)
-> ByteString
-> GetPromotionCodesResponse
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) ->
                                   GetPromotionCodesResponseBody200 -> GetPromotionCodesResponse
GetPromotionCodesResponse200
                                     (GetPromotionCodesResponseBody200 -> GetPromotionCodesResponse)
-> Either String GetPromotionCodesResponseBody200
-> Either String GetPromotionCodesResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String GetPromotionCodesResponseBody200
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            GetPromotionCodesResponseBody200
                                                      )
                                 | 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 -> GetPromotionCodesResponse
GetPromotionCodesResponseDefault
                                     (Error -> GetPromotionCodesResponse)
-> Either String Error -> Either String GetPromotionCodesResponse
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 GetPromotionCodesResponse
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] -> ClientT m (Response ByteString)
forall (m :: * -> *).
MonadHTTP m =>
Text -> Text -> [QueryParameter] -> ClientT 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/promotion_codes")
        [ Text -> Maybe Value -> Text -> Bool -> QueryParameter
StripeAPI.Common.QueryParameter (String -> Text
Data.Text.pack String
"active") (Bool -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (Bool -> Value) -> Maybe Bool -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetPromotionCodesParameters -> Maybe Bool
getPromotionCodesParametersQueryActive GetPromotionCodesParameters
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
"code") (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.<$> GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCode GetPromotionCodesParameters
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
"coupon") (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.<$> GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCoupon GetPromotionCodesParameters
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") (GetPromotionCodesParametersQueryCreated'Variants -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON (GetPromotionCodesParametersQueryCreated'Variants -> Value)
-> Maybe GetPromotionCodesParametersQueryCreated'Variants
-> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> GetPromotionCodesParameters
-> Maybe GetPromotionCodesParametersQueryCreated'Variants
getPromotionCodesParametersQueryCreated GetPromotionCodesParameters
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
"customer") (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.<$> GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCustomer GetPromotionCodesParameters
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
"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.<$> GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryEndingBefore GetPromotionCodesParameters
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.<$> GetPromotionCodesParameters -> Maybe [Text]
getPromotionCodesParametersQueryExpand GetPromotionCodesParameters
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.<$> GetPromotionCodesParameters -> Maybe Int
getPromotionCodesParametersQueryLimit GetPromotionCodesParameters
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.<$> GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryStartingAfter GetPromotionCodesParameters
parameters) (String -> Text
Data.Text.pack String
"form") Bool
GHC.Types.True
        ]
    )

-- | Defines the object schema located at @paths.\/v1\/promotion_codes.GET.parameters@ in the specification.
data GetPromotionCodesParameters = GetPromotionCodesParameters
  { -- | queryActive: Represents the parameter named \'active\'
    --
    -- Filter promotion codes by whether they are active.
    GetPromotionCodesParameters -> Maybe Bool
getPromotionCodesParametersQueryActive :: (GHC.Maybe.Maybe GHC.Types.Bool),
    -- | queryCode: Represents the parameter named \'code\'
    --
    -- Only return promotion codes that have this case-insensitive code.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | queryCoupon: Represents the parameter named \'coupon\'
    --
    -- Only return promotion codes for this coupon.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCoupon :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | queryCreated: Represents the parameter named \'created\'
    --
    -- A filter on the list, based on the object \`created\` field. The value can be a string with an integer Unix timestamp, or it can be a dictionary with a number of different query options.
    GetPromotionCodesParameters
-> Maybe GetPromotionCodesParametersQueryCreated'Variants
getPromotionCodesParametersQueryCreated :: (GHC.Maybe.Maybe GetPromotionCodesParametersQueryCreated'Variants),
    -- | queryCustomer: Represents the parameter named \'customer\'
    --
    -- Only return promotion codes that are restricted to this customer.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCustomer :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | 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
    GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryEndingBefore :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | queryExpand: Represents the parameter named \'expand\'
    --
    -- Specifies which fields in the response should be expanded.
    GetPromotionCodesParameters -> Maybe [Text]
getPromotionCodesParametersQueryExpand :: (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.
    GetPromotionCodesParameters -> Maybe Int
getPromotionCodesParametersQueryLimit :: (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
    GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryStartingAfter :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> GetPromotionCodesParameters -> ShowS
[GetPromotionCodesParameters] -> ShowS
GetPromotionCodesParameters -> String
(Int -> GetPromotionCodesParameters -> ShowS)
-> (GetPromotionCodesParameters -> String)
-> ([GetPromotionCodesParameters] -> ShowS)
-> Show GetPromotionCodesParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPromotionCodesParameters] -> ShowS
$cshowList :: [GetPromotionCodesParameters] -> ShowS
show :: GetPromotionCodesParameters -> String
$cshow :: GetPromotionCodesParameters -> String
showsPrec :: Int -> GetPromotionCodesParameters -> ShowS
$cshowsPrec :: Int -> GetPromotionCodesParameters -> ShowS
GHC.Show.Show,
      GetPromotionCodesParameters -> GetPromotionCodesParameters -> Bool
(GetPromotionCodesParameters
 -> GetPromotionCodesParameters -> Bool)
-> (GetPromotionCodesParameters
    -> GetPromotionCodesParameters -> Bool)
-> Eq GetPromotionCodesParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPromotionCodesParameters -> GetPromotionCodesParameters -> Bool
$c/= :: GetPromotionCodesParameters -> GetPromotionCodesParameters -> Bool
== :: GetPromotionCodesParameters -> GetPromotionCodesParameters -> Bool
$c== :: GetPromotionCodesParameters -> GetPromotionCodesParameters -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON GetPromotionCodesParameters where
  toJSON :: GetPromotionCodesParameters -> Value
toJSON GetPromotionCodesParameters
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"queryActive" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters -> Maybe Bool
getPromotionCodesParametersQueryActive GetPromotionCodesParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryCode" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCode GetPromotionCodesParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryCoupon" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCoupon GetPromotionCodesParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryCreated" Text
-> Maybe GetPromotionCodesParametersQueryCreated'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters
-> Maybe GetPromotionCodesParametersQueryCreated'Variants
getPromotionCodesParametersQueryCreated GetPromotionCodesParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"queryCustomer" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCustomer GetPromotionCodesParameters
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..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryEndingBefore GetPromotionCodesParameters
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..= GetPromotionCodesParameters -> Maybe [Text]
getPromotionCodesParametersQueryExpand GetPromotionCodesParameters
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..= GetPromotionCodesParameters -> Maybe Int
getPromotionCodesParametersQueryLimit GetPromotionCodesParameters
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..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryStartingAfter GetPromotionCodesParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: GetPromotionCodesParameters -> Encoding
toEncoding GetPromotionCodesParameters
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"queryActive" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters -> Maybe Bool
getPromotionCodesParametersQueryActive GetPromotionCodesParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryCode" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCode GetPromotionCodesParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryCoupon" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCoupon GetPromotionCodesParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryCreated" Text
-> Maybe GetPromotionCodesParametersQueryCreated'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters
-> Maybe GetPromotionCodesParametersQueryCreated'Variants
getPromotionCodesParametersQueryCreated GetPromotionCodesParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"queryCustomer" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryCustomer GetPromotionCodesParameters
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..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryEndingBefore GetPromotionCodesParameters
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..= GetPromotionCodesParameters -> Maybe [Text]
getPromotionCodesParametersQueryExpand GetPromotionCodesParameters
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..= GetPromotionCodesParameters -> Maybe Int
getPromotionCodesParametersQueryLimit GetPromotionCodesParameters
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..= GetPromotionCodesParameters -> Maybe Text
getPromotionCodesParametersQueryStartingAfter GetPromotionCodesParameters
obj)))))))))

instance Data.Aeson.Types.FromJSON.FromJSON GetPromotionCodesParameters where
  parseJSON :: Value -> Parser GetPromotionCodesParameters
parseJSON = String
-> (Object -> Parser GetPromotionCodesParameters)
-> Value
-> Parser GetPromotionCodesParameters
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GetPromotionCodesParameters" (\Object
obj -> (((((((((Maybe Bool
 -> Maybe Text
 -> Maybe Text
 -> Maybe GetPromotionCodesParametersQueryCreated'Variants
 -> Maybe Text
 -> Maybe Text
 -> Maybe [Text]
 -> Maybe Int
 -> Maybe Text
 -> GetPromotionCodesParameters)
-> Parser
     (Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe GetPromotionCodesParametersQueryCreated'Variants
      -> Maybe Text
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> GetPromotionCodesParameters)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe GetPromotionCodesParametersQueryCreated'Variants
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Text
-> GetPromotionCodesParameters
GetPromotionCodesParameters Parser
  (Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe GetPromotionCodesParametersQueryCreated'Variants
   -> Maybe Text
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> GetPromotionCodesParameters)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe GetPromotionCodesParametersQueryCreated'Variants
      -> Maybe Text
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> GetPromotionCodesParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryActive")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe GetPromotionCodesParametersQueryCreated'Variants
   -> Maybe Text
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> GetPromotionCodesParameters)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe GetPromotionCodesParametersQueryCreated'Variants
      -> Maybe Text
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> GetPromotionCodesParameters)
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
"queryCode")) Parser
  (Maybe Text
   -> Maybe GetPromotionCodesParametersQueryCreated'Variants
   -> Maybe Text
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> GetPromotionCodesParameters)
-> Parser (Maybe Text)
-> Parser
     (Maybe GetPromotionCodesParametersQueryCreated'Variants
      -> Maybe Text
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> GetPromotionCodesParameters)
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
"queryCoupon")) Parser
  (Maybe GetPromotionCodesParametersQueryCreated'Variants
   -> Maybe Text
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> GetPromotionCodesParameters)
-> Parser (Maybe GetPromotionCodesParametersQueryCreated'Variants)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> GetPromotionCodesParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe GetPromotionCodesParametersQueryCreated'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"queryCreated")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> GetPromotionCodesParameters)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe [Text]
      -> Maybe Int
      -> Maybe Text
      -> GetPromotionCodesParameters)
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
"queryCustomer")) Parser
  (Maybe Text
   -> Maybe [Text]
   -> Maybe Int
   -> Maybe Text
   -> GetPromotionCodesParameters)
-> Parser (Maybe Text)
-> Parser
     (Maybe [Text]
      -> Maybe Int -> Maybe Text -> GetPromotionCodesParameters)
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 -> GetPromotionCodesParameters)
-> Parser (Maybe [Text])
-> Parser (Maybe Int -> Maybe Text -> GetPromotionCodesParameters)
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 -> GetPromotionCodesParameters)
-> Parser (Maybe Int)
-> Parser (Maybe Text -> GetPromotionCodesParameters)
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 -> GetPromotionCodesParameters)
-> Parser (Maybe Text) -> Parser GetPromotionCodesParameters
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"))

-- | Create a new 'GetPromotionCodesParameters' with all required fields.
mkGetPromotionCodesParameters :: GetPromotionCodesParameters
mkGetPromotionCodesParameters :: GetPromotionCodesParameters
mkGetPromotionCodesParameters =
  GetPromotionCodesParameters :: Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe GetPromotionCodesParametersQueryCreated'Variants
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Text
-> GetPromotionCodesParameters
GetPromotionCodesParameters
    { getPromotionCodesParametersQueryActive :: Maybe Bool
getPromotionCodesParametersQueryActive = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryCode :: Maybe Text
getPromotionCodesParametersQueryCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryCoupon :: Maybe Text
getPromotionCodesParametersQueryCoupon = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryCreated :: Maybe GetPromotionCodesParametersQueryCreated'Variants
getPromotionCodesParametersQueryCreated = Maybe GetPromotionCodesParametersQueryCreated'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryCustomer :: Maybe Text
getPromotionCodesParametersQueryCustomer = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryEndingBefore :: Maybe Text
getPromotionCodesParametersQueryEndingBefore = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryExpand :: Maybe [Text]
getPromotionCodesParametersQueryExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryLimit :: Maybe Int
getPromotionCodesParametersQueryLimit = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryStartingAfter :: Maybe Text
getPromotionCodesParametersQueryStartingAfter = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

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

instance Data.Aeson.Types.ToJSON.ToJSON GetPromotionCodesParametersQueryCreated'OneOf1 where
  toJSON :: GetPromotionCodesParametersQueryCreated'OneOf1 -> Value
toJSON GetPromotionCodesParametersQueryCreated'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..= GetPromotionCodesParametersQueryCreated'OneOf1 -> Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Gt GetPromotionCodesParametersQueryCreated'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..= GetPromotionCodesParametersQueryCreated'OneOf1 -> Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Gte GetPromotionCodesParametersQueryCreated'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..= GetPromotionCodesParametersQueryCreated'OneOf1 -> Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Lt GetPromotionCodesParametersQueryCreated'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..= GetPromotionCodesParametersQueryCreated'OneOf1 -> Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Lte GetPromotionCodesParametersQueryCreated'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: GetPromotionCodesParametersQueryCreated'OneOf1 -> Encoding
toEncoding GetPromotionCodesParametersQueryCreated'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..= GetPromotionCodesParametersQueryCreated'OneOf1 -> Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Gt GetPromotionCodesParametersQueryCreated'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..= GetPromotionCodesParametersQueryCreated'OneOf1 -> Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Gte GetPromotionCodesParametersQueryCreated'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..= GetPromotionCodesParametersQueryCreated'OneOf1 -> Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Lt GetPromotionCodesParametersQueryCreated'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..= GetPromotionCodesParametersQueryCreated'OneOf1 -> Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Lte GetPromotionCodesParametersQueryCreated'OneOf1
obj))))

instance Data.Aeson.Types.FromJSON.FromJSON GetPromotionCodesParametersQueryCreated'OneOf1 where
  parseJSON :: Value -> Parser GetPromotionCodesParametersQueryCreated'OneOf1
parseJSON = String
-> (Object
    -> Parser GetPromotionCodesParametersQueryCreated'OneOf1)
-> Value
-> Parser GetPromotionCodesParametersQueryCreated'OneOf1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GetPromotionCodesParametersQueryCreated'OneOf1" (\Object
obj -> ((((Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> GetPromotionCodesParametersQueryCreated'OneOf1)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> GetPromotionCodesParametersQueryCreated'OneOf1)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> GetPromotionCodesParametersQueryCreated'OneOf1
GetPromotionCodesParametersQueryCreated'OneOf1 Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> GetPromotionCodesParametersQueryCreated'OneOf1)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> GetPromotionCodesParametersQueryCreated'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
   -> GetPromotionCodesParametersQueryCreated'OneOf1)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe Int -> GetPromotionCodesParametersQueryCreated'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 -> GetPromotionCodesParametersQueryCreated'OneOf1)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int -> GetPromotionCodesParametersQueryCreated'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 -> GetPromotionCodesParametersQueryCreated'OneOf1)
-> Parser (Maybe Int)
-> Parser GetPromotionCodesParametersQueryCreated'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 'GetPromotionCodesParametersQueryCreated'OneOf1' with all required fields.
mkGetPromotionCodesParametersQueryCreated'OneOf1 :: GetPromotionCodesParametersQueryCreated'OneOf1
mkGetPromotionCodesParametersQueryCreated'OneOf1 :: GetPromotionCodesParametersQueryCreated'OneOf1
mkGetPromotionCodesParametersQueryCreated'OneOf1 =
  GetPromotionCodesParametersQueryCreated'OneOf1 :: Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> GetPromotionCodesParametersQueryCreated'OneOf1
GetPromotionCodesParametersQueryCreated'OneOf1
    { getPromotionCodesParametersQueryCreated'OneOf1Gt :: Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Gt = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryCreated'OneOf1Gte :: Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Gte = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryCreated'OneOf1Lt :: Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Lt = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      getPromotionCodesParametersQueryCreated'OneOf1Lte :: Maybe Int
getPromotionCodesParametersQueryCreated'OneOf1Lte = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the oneOf schema located at @paths.\/v1\/promotion_codes.GET.parameters.properties.queryCreated.anyOf@ in the specification.
--
-- Represents the parameter named \'created\'
--
-- A filter on the list, based on the object \`created\` field. The value can be a string with an integer Unix timestamp, or it can be a dictionary with a number of different query options.
data GetPromotionCodesParametersQueryCreated'Variants
  = GetPromotionCodesParametersQueryCreated'GetPromotionCodesParametersQueryCreated'OneOf1 GetPromotionCodesParametersQueryCreated'OneOf1
  | GetPromotionCodesParametersQueryCreated'Int GHC.Types.Int
  deriving (Int -> GetPromotionCodesParametersQueryCreated'Variants -> ShowS
[GetPromotionCodesParametersQueryCreated'Variants] -> ShowS
GetPromotionCodesParametersQueryCreated'Variants -> String
(Int -> GetPromotionCodesParametersQueryCreated'Variants -> ShowS)
-> (GetPromotionCodesParametersQueryCreated'Variants -> String)
-> ([GetPromotionCodesParametersQueryCreated'Variants] -> ShowS)
-> Show GetPromotionCodesParametersQueryCreated'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPromotionCodesParametersQueryCreated'Variants] -> ShowS
$cshowList :: [GetPromotionCodesParametersQueryCreated'Variants] -> ShowS
show :: GetPromotionCodesParametersQueryCreated'Variants -> String
$cshow :: GetPromotionCodesParametersQueryCreated'Variants -> String
showsPrec :: Int -> GetPromotionCodesParametersQueryCreated'Variants -> ShowS
$cshowsPrec :: Int -> GetPromotionCodesParametersQueryCreated'Variants -> ShowS
GHC.Show.Show, GetPromotionCodesParametersQueryCreated'Variants
-> GetPromotionCodesParametersQueryCreated'Variants -> Bool
(GetPromotionCodesParametersQueryCreated'Variants
 -> GetPromotionCodesParametersQueryCreated'Variants -> Bool)
-> (GetPromotionCodesParametersQueryCreated'Variants
    -> GetPromotionCodesParametersQueryCreated'Variants -> Bool)
-> Eq GetPromotionCodesParametersQueryCreated'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPromotionCodesParametersQueryCreated'Variants
-> GetPromotionCodesParametersQueryCreated'Variants -> Bool
$c/= :: GetPromotionCodesParametersQueryCreated'Variants
-> GetPromotionCodesParametersQueryCreated'Variants -> Bool
== :: GetPromotionCodesParametersQueryCreated'Variants
-> GetPromotionCodesParametersQueryCreated'Variants -> Bool
$c== :: GetPromotionCodesParametersQueryCreated'Variants
-> GetPromotionCodesParametersQueryCreated'Variants -> Bool
GHC.Classes.Eq)

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

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

-- | Represents a response of the operation 'getPromotionCodes'.
--
-- 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), 'GetPromotionCodesResponseError' is used.
data GetPromotionCodesResponse
  = -- | Means either no matching case available or a parse error
    GetPromotionCodesResponseError GHC.Base.String
  | -- | Successful response.
    GetPromotionCodesResponse200 GetPromotionCodesResponseBody200
  | -- | Error response.
    GetPromotionCodesResponseDefault Error
  deriving (Int -> GetPromotionCodesResponse -> ShowS
[GetPromotionCodesResponse] -> ShowS
GetPromotionCodesResponse -> String
(Int -> GetPromotionCodesResponse -> ShowS)
-> (GetPromotionCodesResponse -> String)
-> ([GetPromotionCodesResponse] -> ShowS)
-> Show GetPromotionCodesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPromotionCodesResponse] -> ShowS
$cshowList :: [GetPromotionCodesResponse] -> ShowS
show :: GetPromotionCodesResponse -> String
$cshow :: GetPromotionCodesResponse -> String
showsPrec :: Int -> GetPromotionCodesResponse -> ShowS
$cshowsPrec :: Int -> GetPromotionCodesResponse -> ShowS
GHC.Show.Show, GetPromotionCodesResponse -> GetPromotionCodesResponse -> Bool
(GetPromotionCodesResponse -> GetPromotionCodesResponse -> Bool)
-> (GetPromotionCodesResponse -> GetPromotionCodesResponse -> Bool)
-> Eq GetPromotionCodesResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPromotionCodesResponse -> GetPromotionCodesResponse -> Bool
$c/= :: GetPromotionCodesResponse -> GetPromotionCodesResponse -> Bool
== :: GetPromotionCodesResponse -> GetPromotionCodesResponse -> Bool
$c== :: GetPromotionCodesResponse -> GetPromotionCodesResponse -> Bool
GHC.Classes.Eq)

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

instance Data.Aeson.Types.ToJSON.ToJSON GetPromotionCodesResponseBody200 where
  toJSON :: GetPromotionCodesResponseBody200 -> Value
toJSON GetPromotionCodesResponseBody200
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"data" Text -> [PromotionCode] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesResponseBody200 -> [PromotionCode]
getPromotionCodesResponseBody200Data GetPromotionCodesResponseBody200
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..= GetPromotionCodesResponseBody200 -> Bool
getPromotionCodesResponseBody200HasMore GetPromotionCodesResponseBody200
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..= GetPromotionCodesResponseBody200 -> Text
getPromotionCodesResponseBody200Url GetPromotionCodesResponseBody200
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 :: GetPromotionCodesResponseBody200 -> Encoding
toEncoding GetPromotionCodesResponseBody200
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"data" Text -> [PromotionCode] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GetPromotionCodesResponseBody200 -> [PromotionCode]
getPromotionCodesResponseBody200Data GetPromotionCodesResponseBody200
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..= GetPromotionCodesResponseBody200 -> Bool
getPromotionCodesResponseBody200HasMore GetPromotionCodesResponseBody200
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..= GetPromotionCodesResponseBody200 -> Text
getPromotionCodesResponseBody200Url GetPromotionCodesResponseBody200
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 GetPromotionCodesResponseBody200 where
  parseJSON :: Value -> Parser GetPromotionCodesResponseBody200
parseJSON = String
-> (Object -> Parser GetPromotionCodesResponseBody200)
-> Value
-> Parser GetPromotionCodesResponseBody200
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GetPromotionCodesResponseBody200" (\Object
obj -> ((([PromotionCode]
 -> Bool -> Text -> GetPromotionCodesResponseBody200)
-> Parser
     ([PromotionCode]
      -> Bool -> Text -> GetPromotionCodesResponseBody200)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure [PromotionCode] -> Bool -> Text -> GetPromotionCodesResponseBody200
GetPromotionCodesResponseBody200 Parser
  ([PromotionCode]
   -> Bool -> Text -> GetPromotionCodesResponseBody200)
-> Parser [PromotionCode]
-> Parser (Bool -> Text -> GetPromotionCodesResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser [PromotionCode]
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"data")) Parser (Bool -> Text -> GetPromotionCodesResponseBody200)
-> Parser Bool -> Parser (Text -> GetPromotionCodesResponseBody200)
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 -> GetPromotionCodesResponseBody200)
-> Parser Text -> Parser GetPromotionCodesResponseBody200
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 'GetPromotionCodesResponseBody200' with all required fields.
mkGetPromotionCodesResponseBody200 ::
  -- | 'getPromotionCodesResponseBody200Data'
  [PromotionCode] ->
  -- | 'getPromotionCodesResponseBody200HasMore'
  GHC.Types.Bool ->
  -- | 'getPromotionCodesResponseBody200Url'
  Data.Text.Internal.Text ->
  GetPromotionCodesResponseBody200
mkGetPromotionCodesResponseBody200 :: [PromotionCode] -> Bool -> Text -> GetPromotionCodesResponseBody200
mkGetPromotionCodesResponseBody200 [PromotionCode]
getPromotionCodesResponseBody200Data Bool
getPromotionCodesResponseBody200HasMore Text
getPromotionCodesResponseBody200Url =
  GetPromotionCodesResponseBody200 :: [PromotionCode] -> Bool -> Text -> GetPromotionCodesResponseBody200
GetPromotionCodesResponseBody200
    { getPromotionCodesResponseBody200Data :: [PromotionCode]
getPromotionCodesResponseBody200Data = [PromotionCode]
getPromotionCodesResponseBody200Data,
      getPromotionCodesResponseBody200HasMore :: Bool
getPromotionCodesResponseBody200HasMore = Bool
getPromotionCodesResponseBody200HasMore,
      getPromotionCodesResponseBody200Url :: Text
getPromotionCodesResponseBody200Url = Text
getPromotionCodesResponseBody200Url
    }