{-# 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 DeliveryEstimate
module StripeAPI.Types.DeliveryEstimate 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.delivery_estimate@ in the specification.
data DeliveryEstimate = DeliveryEstimate
  { -- | date: If \`type\` is \`\"exact\"\`, \`date\` will be the expected delivery date in the format YYYY-MM-DD.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    DeliveryEstimate -> Maybe Text
deliveryEstimateDate :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | earliest: If \`type\` is \`\"range\"\`, \`earliest\` will be be the earliest delivery date in the format YYYY-MM-DD.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    DeliveryEstimate -> Maybe Text
deliveryEstimateEarliest :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | latest: If \`type\` is \`\"range\"\`, \`latest\` will be the latest delivery date in the format YYYY-MM-DD.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    DeliveryEstimate -> Maybe Text
deliveryEstimateLatest :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | type: The type of estimate. Must be either \`\"range\"\` or \`\"exact\"\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    DeliveryEstimate -> Text
deliveryEstimateType :: Data.Text.Internal.Text
  }
  deriving
    ( Int -> DeliveryEstimate -> ShowS
[DeliveryEstimate] -> ShowS
DeliveryEstimate -> String
(Int -> DeliveryEstimate -> ShowS)
-> (DeliveryEstimate -> String)
-> ([DeliveryEstimate] -> ShowS)
-> Show DeliveryEstimate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeliveryEstimate] -> ShowS
$cshowList :: [DeliveryEstimate] -> ShowS
show :: DeliveryEstimate -> String
$cshow :: DeliveryEstimate -> String
showsPrec :: Int -> DeliveryEstimate -> ShowS
$cshowsPrec :: Int -> DeliveryEstimate -> ShowS
GHC.Show.Show,
      DeliveryEstimate -> DeliveryEstimate -> Bool
(DeliveryEstimate -> DeliveryEstimate -> Bool)
-> (DeliveryEstimate -> DeliveryEstimate -> Bool)
-> Eq DeliveryEstimate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeliveryEstimate -> DeliveryEstimate -> Bool
$c/= :: DeliveryEstimate -> DeliveryEstimate -> Bool
== :: DeliveryEstimate -> DeliveryEstimate -> Bool
$c== :: DeliveryEstimate -> DeliveryEstimate -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON DeliveryEstimate where
  toJSON :: DeliveryEstimate -> Value
toJSON DeliveryEstimate
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"date" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeliveryEstimate -> Maybe Text
deliveryEstimateDate DeliveryEstimate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"earliest" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeliveryEstimate -> Maybe Text
deliveryEstimateEarliest DeliveryEstimate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"latest" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeliveryEstimate -> Maybe Text
deliveryEstimateLatest DeliveryEstimate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeliveryEstimate -> Text
deliveryEstimateType DeliveryEstimate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: DeliveryEstimate -> Encoding
toEncoding DeliveryEstimate
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"date" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeliveryEstimate -> Maybe Text
deliveryEstimateDate DeliveryEstimate
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"earliest" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeliveryEstimate -> Maybe Text
deliveryEstimateEarliest DeliveryEstimate
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"latest" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeliveryEstimate -> Maybe Text
deliveryEstimateLatest DeliveryEstimate
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"type" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeliveryEstimate -> Text
deliveryEstimateType DeliveryEstimate
obj))))

instance Data.Aeson.Types.FromJSON.FromJSON DeliveryEstimate where
  parseJSON :: Value -> Parser DeliveryEstimate
parseJSON = String
-> (Object -> Parser DeliveryEstimate)
-> Value
-> Parser DeliveryEstimate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"DeliveryEstimate" (\Object
obj -> ((((Maybe Text
 -> Maybe Text -> Maybe Text -> Text -> DeliveryEstimate)
-> Parser
     (Maybe Text
      -> Maybe Text -> Maybe Text -> Text -> DeliveryEstimate)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text -> Maybe Text -> Maybe Text -> Text -> DeliveryEstimate
DeliveryEstimate Parser
  (Maybe Text
   -> Maybe Text -> Maybe Text -> Text -> DeliveryEstimate)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Text -> Text -> DeliveryEstimate)
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
"date")) Parser (Maybe Text -> Maybe Text -> Text -> DeliveryEstimate)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Text -> DeliveryEstimate)
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
"earliest")) Parser (Maybe Text -> Text -> DeliveryEstimate)
-> Parser (Maybe Text) -> Parser (Text -> DeliveryEstimate)
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
"latest")) Parser (Text -> DeliveryEstimate)
-> Parser Text -> Parser DeliveryEstimate
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
"type"))

-- | Create a new 'DeliveryEstimate' with all required fields.
mkDeliveryEstimate ::
  -- | 'deliveryEstimateType'
  Data.Text.Internal.Text ->
  DeliveryEstimate
mkDeliveryEstimate :: Text -> DeliveryEstimate
mkDeliveryEstimate Text
deliveryEstimateType =
  DeliveryEstimate :: Maybe Text -> Maybe Text -> Maybe Text -> Text -> DeliveryEstimate
DeliveryEstimate
    { deliveryEstimateDate :: Maybe Text
deliveryEstimateDate = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      deliveryEstimateEarliest :: Maybe Text
deliveryEstimateEarliest = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      deliveryEstimateLatest :: Maybe Text
deliveryEstimateLatest = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      deliveryEstimateType :: Text
deliveryEstimateType = Text
deliveryEstimateType
    }