{-# 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 types generated from the schema Radar_ValueListItem
module StripeAPI.Types.Radar_ValueListItem where

import qualified Control.Monad.Fail
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.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 GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified StripeAPI.Common
import StripeAPI.TypeAlias
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | Defines the object schema located at @components.schemas.radar.value_list_item@ in the specification.
--
-- Value list items allow you to add specific values to a given Radar value list, which can then be used in rules.
--
-- Related guide: [Managing List Items](https:\/\/stripe.com\/docs\/radar\/lists\#managing-list-items).
data Radar'valueListItem = Radar'valueListItem
  { -- | created: Time at which the object was created. Measured in seconds since the Unix epoch.
    Radar'valueListItem -> Int
radar'valueListItemCreated :: GHC.Types.Int,
    -- | created_by: The name or email address of the user who added this item to the value list.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    Radar'valueListItem -> Text
radar'valueListItemCreatedBy :: Data.Text.Internal.Text,
    -- | id: Unique identifier for the object.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    Radar'valueListItem -> Text
radar'valueListItemId :: Data.Text.Internal.Text,
    -- | livemode: Has the value \`true\` if the object exists in live mode or the value \`false\` if the object exists in test mode.
    Radar'valueListItem -> Bool
radar'valueListItemLivemode :: GHC.Types.Bool,
    -- | value: The value of the item.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    Radar'valueListItem -> Text
radar'valueListItemValue :: Data.Text.Internal.Text,
    -- | value_list: The identifier of the value list this item belongs to.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    Radar'valueListItem -> Text
radar'valueListItemValueList :: Data.Text.Internal.Text
  }
  deriving
    ( Int -> Radar'valueListItem -> ShowS
[Radar'valueListItem] -> ShowS
Radar'valueListItem -> String
(Int -> Radar'valueListItem -> ShowS)
-> (Radar'valueListItem -> String)
-> ([Radar'valueListItem] -> ShowS)
-> Show Radar'valueListItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Radar'valueListItem] -> ShowS
$cshowList :: [Radar'valueListItem] -> ShowS
show :: Radar'valueListItem -> String
$cshow :: Radar'valueListItem -> String
showsPrec :: Int -> Radar'valueListItem -> ShowS
$cshowsPrec :: Int -> Radar'valueListItem -> ShowS
GHC.Show.Show,
      Radar'valueListItem -> Radar'valueListItem -> Bool
(Radar'valueListItem -> Radar'valueListItem -> Bool)
-> (Radar'valueListItem -> Radar'valueListItem -> Bool)
-> Eq Radar'valueListItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Radar'valueListItem -> Radar'valueListItem -> Bool
$c/= :: Radar'valueListItem -> Radar'valueListItem -> Bool
== :: Radar'valueListItem -> Radar'valueListItem -> Bool
$c== :: Radar'valueListItem -> Radar'valueListItem -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON Radar'valueListItem where
  toJSON :: Radar'valueListItem -> Value
toJSON Radar'valueListItem
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"created" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Int
radar'valueListItemCreated Radar'valueListItem
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"created_by" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Text
radar'valueListItemCreatedBy Radar'valueListItem
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"id" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Text
radar'valueListItemId Radar'valueListItem
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"livemode" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Bool
radar'valueListItemLivemode Radar'valueListItem
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"value" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Text
radar'valueListItemValue Radar'valueListItem
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"value_list" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Text
radar'valueListItemValueList Radar'valueListItem
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
"radar.value_list_item" Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: Radar'valueListItem -> Encoding
toEncoding Radar'valueListItem
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"created" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Int
radar'valueListItemCreated Radar'valueListItem
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"created_by" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Text
radar'valueListItemCreatedBy Radar'valueListItem
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"id" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Text
radar'valueListItemId Radar'valueListItem
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"livemode" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Bool
radar'valueListItemLivemode Radar'valueListItem
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"value" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Text
radar'valueListItemValue Radar'valueListItem
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"value_list" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Radar'valueListItem -> Text
radar'valueListItemValueList Radar'valueListItem
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
"radar.value_list_item")))))))

instance Data.Aeson.Types.FromJSON.FromJSON Radar'valueListItem where
  parseJSON :: Value -> Parser Radar'valueListItem
parseJSON = String
-> (Object -> Parser Radar'valueListItem)
-> Value
-> Parser Radar'valueListItem
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Radar'valueListItem" (\Object
obj -> ((((((Int
 -> Text -> Text -> Bool -> Text -> Text -> Radar'valueListItem)
-> Parser
     (Int
      -> Text -> Text -> Bool -> Text -> Text -> Radar'valueListItem)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Int -> Text -> Text -> Bool -> Text -> Text -> Radar'valueListItem
Radar'valueListItem Parser
  (Int
   -> Text -> Text -> Bool -> Text -> Text -> Radar'valueListItem)
-> Parser Int
-> Parser
     (Text -> Text -> Bool -> Text -> Text -> Radar'valueListItem)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"created")) Parser
  (Text -> Text -> Bool -> Text -> Text -> Radar'valueListItem)
-> Parser Text
-> Parser (Text -> Bool -> Text -> Text -> Radar'valueListItem)
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
"created_by")) Parser (Text -> Bool -> Text -> Text -> Radar'valueListItem)
-> Parser Text
-> Parser (Bool -> Text -> Text -> Radar'valueListItem)
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
"id")) Parser (Bool -> Text -> Text -> Radar'valueListItem)
-> Parser Bool -> Parser (Text -> Text -> Radar'valueListItem)
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
"livemode")) Parser (Text -> Text -> Radar'valueListItem)
-> Parser Text -> Parser (Text -> Radar'valueListItem)
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
"value")) Parser (Text -> Radar'valueListItem)
-> Parser Text -> Parser Radar'valueListItem
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
"value_list"))

-- | Create a new 'Radar'valueListItem' with all required fields.
mkRadar'valueListItem ::
  -- | 'radar'valueListItemCreated'
  GHC.Types.Int ->
  -- | 'radar'valueListItemCreatedBy'
  Data.Text.Internal.Text ->
  -- | 'radar'valueListItemId'
  Data.Text.Internal.Text ->
  -- | 'radar'valueListItemLivemode'
  GHC.Types.Bool ->
  -- | 'radar'valueListItemValue'
  Data.Text.Internal.Text ->
  -- | 'radar'valueListItemValueList'
  Data.Text.Internal.Text ->
  Radar'valueListItem
mkRadar'valueListItem :: Int -> Text -> Text -> Bool -> Text -> Text -> Radar'valueListItem
mkRadar'valueListItem Int
radar'valueListItemCreated Text
radar'valueListItemCreatedBy Text
radar'valueListItemId Bool
radar'valueListItemLivemode Text
radar'valueListItemValue Text
radar'valueListItemValueList =
  Radar'valueListItem :: Int -> Text -> Text -> Bool -> Text -> Text -> Radar'valueListItem
Radar'valueListItem
    { radar'valueListItemCreated :: Int
radar'valueListItemCreated = Int
radar'valueListItemCreated,
      radar'valueListItemCreatedBy :: Text
radar'valueListItemCreatedBy = Text
radar'valueListItemCreatedBy,
      radar'valueListItemId :: Text
radar'valueListItemId = Text
radar'valueListItemId,
      radar'valueListItemLivemode :: Bool
radar'valueListItemLivemode = Bool
radar'valueListItemLivemode,
      radar'valueListItemValue :: Text
radar'valueListItemValue = Text
radar'valueListItemValue,
      radar'valueListItemValueList :: Text
radar'valueListItemValueList = Text
radar'valueListItemValueList
    }