{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.InvoiceCreate 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
import qualified Data.ByteString as Data.ByteString.Internal
import qualified Data.Foldable
import qualified Data.Functor
import qualified Data.Maybe
import qualified Data.Scientific
import qualified Data.Text
import qualified Data.Text as 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 RecurlyClient.Common
import RecurlyClient.TypeAlias
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data InvoiceCreate = InvoiceCreate
{ InvoiceCreate -> Maybe Text
invoiceCreateBusiness_entity_code :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, InvoiceCreate -> Maybe Text
invoiceCreateBusiness_entity_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, InvoiceCreate -> Maybe Text
invoiceCreateCharge_customer_notes :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, InvoiceCreate -> Maybe InvoiceCreateCollection_method
invoiceCreateCollection_method :: (GHC.Maybe.Maybe InvoiceCreateCollection_method)
, InvoiceCreate -> Maybe Text
invoiceCreateCredit_customer_notes :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, InvoiceCreate -> Text
invoiceCreateCurrency :: Data.Text.Internal.Text
, InvoiceCreate -> Maybe Int
invoiceCreateNet_terms :: (GHC.Maybe.Maybe GHC.Types.Int)
, InvoiceCreate -> Maybe InvoiceCreateNet_terms_type
invoiceCreateNet_terms_type :: (GHC.Maybe.Maybe InvoiceCreateNet_terms_type)
, InvoiceCreate -> Maybe Text
invoiceCreatePo_number :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, InvoiceCreate -> Maybe Text
invoiceCreateTerms_and_conditions :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, InvoiceCreate -> Maybe Text
invoiceCreateVat_reverse_charge_notes :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
}
deriving
( Int -> InvoiceCreate -> ShowS
[InvoiceCreate] -> ShowS
InvoiceCreate -> String
(Int -> InvoiceCreate -> ShowS)
-> (InvoiceCreate -> String)
-> ([InvoiceCreate] -> ShowS)
-> Show InvoiceCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvoiceCreate -> ShowS
showsPrec :: Int -> InvoiceCreate -> ShowS
$cshow :: InvoiceCreate -> String
show :: InvoiceCreate -> String
$cshowList :: [InvoiceCreate] -> ShowS
showList :: [InvoiceCreate] -> ShowS
GHC.Show.Show
, InvoiceCreate -> InvoiceCreate -> Bool
(InvoiceCreate -> InvoiceCreate -> Bool)
-> (InvoiceCreate -> InvoiceCreate -> Bool) -> Eq InvoiceCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvoiceCreate -> InvoiceCreate -> Bool
== :: InvoiceCreate -> InvoiceCreate -> Bool
$c/= :: InvoiceCreate -> InvoiceCreate -> Bool
/= :: InvoiceCreate -> InvoiceCreate -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON InvoiceCreate where
toJSON :: InvoiceCreate -> Value
toJSON InvoiceCreate
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"business_entity_code" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateBusiness_entity_code InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"business_entity_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateBusiness_entity_id InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"charge_customer_notes" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateCharge_customer_notes InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (InvoiceCreateCollection_method -> [Pair])
-> Maybe InvoiceCreateCollection_method
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (InvoiceCreateCollection_method -> Pair)
-> InvoiceCreateCollection_method
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"collection_method" Key -> InvoiceCreateCollection_method -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe InvoiceCreateCollection_method
invoiceCreateCollection_method InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"credit_customer_notes" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateCredit_customer_notes InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"currency" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= InvoiceCreate -> Text
invoiceCreateCurrency InvoiceCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Int -> Pair) -> Int -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"net_terms" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Int
invoiceCreateNet_terms InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (InvoiceCreateNet_terms_type -> [Pair])
-> Maybe InvoiceCreateNet_terms_type
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (InvoiceCreateNet_terms_type -> Pair)
-> InvoiceCreateNet_terms_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"net_terms_type" Key -> InvoiceCreateNet_terms_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe InvoiceCreateNet_terms_type
invoiceCreateNet_terms_type InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"po_number" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreatePo_number InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"terms_and_conditions" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateTerms_and_conditions InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"vat_reverse_charge_notes" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateVat_reverse_charge_notes InvoiceCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: InvoiceCreate -> Encoding
toEncoding InvoiceCreate
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ([Series] -> Series
forall a. Monoid a => [a] -> a
GHC.Base.mconcat ([[Series]] -> [Series]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"business_entity_code" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateBusiness_entity_code InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"business_entity_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateBusiness_entity_id InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"charge_customer_notes" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateCharge_customer_notes InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (InvoiceCreateCollection_method -> [Series])
-> Maybe InvoiceCreateCollection_method
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (InvoiceCreateCollection_method -> Series)
-> InvoiceCreateCollection_method
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"collection_method" Key -> InvoiceCreateCollection_method -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe InvoiceCreateCollection_method
invoiceCreateCollection_method InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"credit_customer_notes" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateCredit_customer_notes InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"currency" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= InvoiceCreate -> Text
invoiceCreateCurrency InvoiceCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Int -> [Series]) -> Maybe Int -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Int -> Series) -> Int -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"net_terms" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Int
invoiceCreateNet_terms InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (InvoiceCreateNet_terms_type -> [Series])
-> Maybe InvoiceCreateNet_terms_type
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (InvoiceCreateNet_terms_type -> Series)
-> InvoiceCreateNet_terms_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"net_terms_type" Key -> InvoiceCreateNet_terms_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe InvoiceCreateNet_terms_type
invoiceCreateNet_terms_type InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"po_number" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreatePo_number InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"terms_and_conditions" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateTerms_and_conditions InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"vat_reverse_charge_notes" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (InvoiceCreate -> Maybe Text
invoiceCreateVat_reverse_charge_notes InvoiceCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON InvoiceCreate where
parseJSON :: Value -> Parser InvoiceCreate
parseJSON = String
-> (Object -> Parser InvoiceCreate)
-> Value
-> Parser InvoiceCreate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"InvoiceCreate" (\Object
obj -> (((((((((((Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate
InvoiceCreate Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"business_entity_code")) Parser
(Maybe Text
-> Maybe Text
-> Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"business_entity_id")) Parser
(Maybe Text
-> Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"charge_customer_notes")) Parser
(Maybe InvoiceCreateCollection_method
-> Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
-> Parser (Maybe InvoiceCreateCollection_method)
-> Parser
(Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe InvoiceCreateCollection_method)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"collection_method")) Parser
(Maybe Text
-> Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
-> Parser (Maybe Text)
-> Parser
(Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"credit_customer_notes")) Parser
(Text
-> Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
-> Parser Text
-> Parser
(Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"currency")) Parser
(Maybe Int
-> Maybe InvoiceCreateNet_terms_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> InvoiceCreate)
-> Parser (Maybe Int)
-> Parser
(Maybe InvoiceCreateNet_terms_type
-> Maybe Text -> Maybe Text -> Maybe Text -> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"net_terms")) Parser
(Maybe InvoiceCreateNet_terms_type
-> Maybe Text -> Maybe Text -> Maybe Text -> InvoiceCreate)
-> Parser (Maybe InvoiceCreateNet_terms_type)
-> Parser (Maybe Text -> Maybe Text -> Maybe Text -> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe InvoiceCreateNet_terms_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"net_terms_type")) Parser (Maybe Text -> Maybe Text -> Maybe Text -> InvoiceCreate)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Text -> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"po_number")) Parser (Maybe Text -> Maybe Text -> InvoiceCreate)
-> Parser (Maybe Text) -> Parser (Maybe Text -> InvoiceCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"terms_and_conditions")) Parser (Maybe Text -> InvoiceCreate)
-> Parser (Maybe Text) -> Parser InvoiceCreate
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"vat_reverse_charge_notes"))
mkInvoiceCreate ::
Data.Text.Internal.Text ->
InvoiceCreate
mkInvoiceCreate :: Text -> InvoiceCreate
mkInvoiceCreate Text
invoiceCreateCurrency =
InvoiceCreate
{ invoiceCreateBusiness_entity_code :: Maybe Text
invoiceCreateBusiness_entity_code = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreateBusiness_entity_id :: Maybe Text
invoiceCreateBusiness_entity_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreateCharge_customer_notes :: Maybe Text
invoiceCreateCharge_customer_notes = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreateCollection_method :: Maybe InvoiceCreateCollection_method
invoiceCreateCollection_method = Maybe InvoiceCreateCollection_method
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreateCredit_customer_notes :: Maybe Text
invoiceCreateCredit_customer_notes = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreateCurrency :: Text
invoiceCreateCurrency = Text
invoiceCreateCurrency
, invoiceCreateNet_terms :: Maybe Int
invoiceCreateNet_terms = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreateNet_terms_type :: Maybe InvoiceCreateNet_terms_type
invoiceCreateNet_terms_type = Maybe InvoiceCreateNet_terms_type
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreatePo_number :: Maybe Text
invoiceCreatePo_number = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreateTerms_and_conditions :: Maybe Text
invoiceCreateTerms_and_conditions = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, invoiceCreateVat_reverse_charge_notes :: Maybe Text
invoiceCreateVat_reverse_charge_notes = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
}
data InvoiceCreateCollection_method
=
InvoiceCreateCollection_methodOther Data.Aeson.Types.Internal.Value
|
InvoiceCreateCollection_methodTyped Data.Text.Internal.Text
|
InvoiceCreateCollection_methodEnumAutomatic
|
InvoiceCreateCollection_methodEnumManual
deriving (Int -> InvoiceCreateCollection_method -> ShowS
[InvoiceCreateCollection_method] -> ShowS
InvoiceCreateCollection_method -> String
(Int -> InvoiceCreateCollection_method -> ShowS)
-> (InvoiceCreateCollection_method -> String)
-> ([InvoiceCreateCollection_method] -> ShowS)
-> Show InvoiceCreateCollection_method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvoiceCreateCollection_method -> ShowS
showsPrec :: Int -> InvoiceCreateCollection_method -> ShowS
$cshow :: InvoiceCreateCollection_method -> String
show :: InvoiceCreateCollection_method -> String
$cshowList :: [InvoiceCreateCollection_method] -> ShowS
showList :: [InvoiceCreateCollection_method] -> ShowS
GHC.Show.Show, InvoiceCreateCollection_method
-> InvoiceCreateCollection_method -> Bool
(InvoiceCreateCollection_method
-> InvoiceCreateCollection_method -> Bool)
-> (InvoiceCreateCollection_method
-> InvoiceCreateCollection_method -> Bool)
-> Eq InvoiceCreateCollection_method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvoiceCreateCollection_method
-> InvoiceCreateCollection_method -> Bool
== :: InvoiceCreateCollection_method
-> InvoiceCreateCollection_method -> Bool
$c/= :: InvoiceCreateCollection_method
-> InvoiceCreateCollection_method -> Bool
/= :: InvoiceCreateCollection_method
-> InvoiceCreateCollection_method -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON InvoiceCreateCollection_method where
toJSON :: InvoiceCreateCollection_method -> Value
toJSON (InvoiceCreateCollection_methodOther Value
val) = Value
val
toJSON (InvoiceCreateCollection_methodTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (InvoiceCreateCollection_method
InvoiceCreateCollection_methodEnumAutomatic) = Value
"automatic"
toJSON (InvoiceCreateCollection_method
InvoiceCreateCollection_methodEnumManual) = Value
"manual"
instance Data.Aeson.Types.FromJSON.FromJSON InvoiceCreateCollection_method where
parseJSON :: Value -> Parser InvoiceCreateCollection_method
parseJSON Value
val =
InvoiceCreateCollection_method
-> Parser InvoiceCreateCollection_method
forall a. a -> Parser a
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
"automatic" -> InvoiceCreateCollection_method
InvoiceCreateCollection_methodEnumAutomatic
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"manual" -> InvoiceCreateCollection_method
InvoiceCreateCollection_methodEnumManual
| Bool
GHC.Base.otherwise -> Value -> InvoiceCreateCollection_method
InvoiceCreateCollection_methodOther Value
val
)
data InvoiceCreateNet_terms_type
=
InvoiceCreateNet_terms_typeOther Data.Aeson.Types.Internal.Value
|
InvoiceCreateNet_terms_typeTyped Data.Text.Internal.Text
|
InvoiceCreateNet_terms_typeEnumNet
|
InvoiceCreateNet_terms_typeEnumEom
deriving (Int -> InvoiceCreateNet_terms_type -> ShowS
[InvoiceCreateNet_terms_type] -> ShowS
InvoiceCreateNet_terms_type -> String
(Int -> InvoiceCreateNet_terms_type -> ShowS)
-> (InvoiceCreateNet_terms_type -> String)
-> ([InvoiceCreateNet_terms_type] -> ShowS)
-> Show InvoiceCreateNet_terms_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvoiceCreateNet_terms_type -> ShowS
showsPrec :: Int -> InvoiceCreateNet_terms_type -> ShowS
$cshow :: InvoiceCreateNet_terms_type -> String
show :: InvoiceCreateNet_terms_type -> String
$cshowList :: [InvoiceCreateNet_terms_type] -> ShowS
showList :: [InvoiceCreateNet_terms_type] -> ShowS
GHC.Show.Show, InvoiceCreateNet_terms_type -> InvoiceCreateNet_terms_type -> Bool
(InvoiceCreateNet_terms_type
-> InvoiceCreateNet_terms_type -> Bool)
-> (InvoiceCreateNet_terms_type
-> InvoiceCreateNet_terms_type -> Bool)
-> Eq InvoiceCreateNet_terms_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvoiceCreateNet_terms_type -> InvoiceCreateNet_terms_type -> Bool
== :: InvoiceCreateNet_terms_type -> InvoiceCreateNet_terms_type -> Bool
$c/= :: InvoiceCreateNet_terms_type -> InvoiceCreateNet_terms_type -> Bool
/= :: InvoiceCreateNet_terms_type -> InvoiceCreateNet_terms_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON InvoiceCreateNet_terms_type where
toJSON :: InvoiceCreateNet_terms_type -> Value
toJSON (InvoiceCreateNet_terms_typeOther Value
val) = Value
val
toJSON (InvoiceCreateNet_terms_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (InvoiceCreateNet_terms_type
InvoiceCreateNet_terms_typeEnumNet) = Value
"net"
toJSON (InvoiceCreateNet_terms_type
InvoiceCreateNet_terms_typeEnumEom) = Value
"eom"
instance Data.Aeson.Types.FromJSON.FromJSON InvoiceCreateNet_terms_type where
parseJSON :: Value -> Parser InvoiceCreateNet_terms_type
parseJSON Value
val =
InvoiceCreateNet_terms_type -> Parser InvoiceCreateNet_terms_type
forall a. a -> Parser a
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
"net" -> InvoiceCreateNet_terms_type
InvoiceCreateNet_terms_typeEnumNet
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"eom" -> InvoiceCreateNet_terms_type
InvoiceCreateNet_terms_typeEnumEom
| Bool
GHC.Base.otherwise -> Value -> InvoiceCreateNet_terms_type
InvoiceCreateNet_terms_typeOther Value
val
)