{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.GeneralLedgerAccount 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 GeneralLedgerAccount = GeneralLedgerAccount
{ GeneralLedgerAccount -> Maybe GeneralLedgerAccountAccount_type
generalLedgerAccountAccount_type :: (GHC.Maybe.Maybe GeneralLedgerAccountAccount_type)
, GeneralLedgerAccount -> Maybe Text
generalLedgerAccountCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, GeneralLedgerAccount -> Maybe JsonDateTime
generalLedgerAccountCreated_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, GeneralLedgerAccount -> Maybe Text
generalLedgerAccountDescription :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, GeneralLedgerAccount -> Maybe Text
generalLedgerAccountId :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, GeneralLedgerAccount -> Maybe Text
generalLedgerAccountObject :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, GeneralLedgerAccount -> Maybe JsonDateTime
generalLedgerAccountUpdated_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
}
deriving
( Int -> GeneralLedgerAccount -> ShowS
[GeneralLedgerAccount] -> ShowS
GeneralLedgerAccount -> String
(Int -> GeneralLedgerAccount -> ShowS)
-> (GeneralLedgerAccount -> String)
-> ([GeneralLedgerAccount] -> ShowS)
-> Show GeneralLedgerAccount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GeneralLedgerAccount -> ShowS
showsPrec :: Int -> GeneralLedgerAccount -> ShowS
$cshow :: GeneralLedgerAccount -> String
show :: GeneralLedgerAccount -> String
$cshowList :: [GeneralLedgerAccount] -> ShowS
showList :: [GeneralLedgerAccount] -> ShowS
GHC.Show.Show
, GeneralLedgerAccount -> GeneralLedgerAccount -> Bool
(GeneralLedgerAccount -> GeneralLedgerAccount -> Bool)
-> (GeneralLedgerAccount -> GeneralLedgerAccount -> Bool)
-> Eq GeneralLedgerAccount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GeneralLedgerAccount -> GeneralLedgerAccount -> Bool
== :: GeneralLedgerAccount -> GeneralLedgerAccount -> Bool
$c/= :: GeneralLedgerAccount -> GeneralLedgerAccount -> Bool
/= :: GeneralLedgerAccount -> GeneralLedgerAccount -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON GeneralLedgerAccount where
toJSON :: GeneralLedgerAccount -> Value
toJSON GeneralLedgerAccount
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair]
-> (GeneralLedgerAccountAccount_type -> [Pair])
-> Maybe GeneralLedgerAccountAccount_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])
-> (GeneralLedgerAccountAccount_type -> Pair)
-> GeneralLedgerAccountAccount_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"account_type" Key -> GeneralLedgerAccountAccount_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe GeneralLedgerAccountAccount_type
generalLedgerAccountAccount_type GeneralLedgerAccount
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
"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..=)) (GeneralLedgerAccount -> Maybe Text
generalLedgerAccountCode GeneralLedgerAccount
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"created_at" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe JsonDateTime
generalLedgerAccountCreated_at GeneralLedgerAccount
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
"description" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe Text
generalLedgerAccountDescription GeneralLedgerAccount
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
"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..=)) (GeneralLedgerAccount -> Maybe Text
generalLedgerAccountId GeneralLedgerAccount
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
"object" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe Text
generalLedgerAccountObject GeneralLedgerAccount
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"updated_at" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe JsonDateTime
generalLedgerAccountUpdated_at GeneralLedgerAccount
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: GeneralLedgerAccount -> Encoding
toEncoding GeneralLedgerAccount
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]
-> (GeneralLedgerAccountAccount_type -> [Series])
-> Maybe GeneralLedgerAccountAccount_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])
-> (GeneralLedgerAccountAccount_type -> Series)
-> GeneralLedgerAccountAccount_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"account_type" Key -> GeneralLedgerAccountAccount_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe GeneralLedgerAccountAccount_type
generalLedgerAccountAccount_type GeneralLedgerAccount
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
"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..=)) (GeneralLedgerAccount -> Maybe Text
generalLedgerAccountCode GeneralLedgerAccount
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"created_at" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe JsonDateTime
generalLedgerAccountCreated_at GeneralLedgerAccount
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
"description" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe Text
generalLedgerAccountDescription GeneralLedgerAccount
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
"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..=)) (GeneralLedgerAccount -> Maybe Text
generalLedgerAccountId GeneralLedgerAccount
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
"object" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe Text
generalLedgerAccountObject GeneralLedgerAccount
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"updated_at" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (GeneralLedgerAccount -> Maybe JsonDateTime
generalLedgerAccountUpdated_at GeneralLedgerAccount
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON GeneralLedgerAccount where
parseJSON :: Value -> Parser GeneralLedgerAccount
parseJSON = String
-> (Object -> Parser GeneralLedgerAccount)
-> Value
-> Parser GeneralLedgerAccount
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GeneralLedgerAccount" (\Object
obj -> (((((((Maybe GeneralLedgerAccountAccount_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
-> Parser
(Maybe GeneralLedgerAccountAccount_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe GeneralLedgerAccountAccount_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount
GeneralLedgerAccount Parser
(Maybe GeneralLedgerAccountAccount_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
-> Parser (Maybe GeneralLedgerAccountAccount_type)
-> Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
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 GeneralLedgerAccountAccount_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"account_type")) Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
-> Parser (Maybe Text)
-> Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
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
"code")) Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
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 JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"created_at")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> GeneralLedgerAccount)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text -> Maybe JsonDateTime -> GeneralLedgerAccount)
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
"description")) Parser
(Maybe Text
-> Maybe Text -> Maybe JsonDateTime -> GeneralLedgerAccount)
-> Parser (Maybe Text)
-> Parser
(Maybe Text -> Maybe JsonDateTime -> GeneralLedgerAccount)
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
"id")) Parser (Maybe Text -> Maybe JsonDateTime -> GeneralLedgerAccount)
-> Parser (Maybe Text)
-> Parser (Maybe JsonDateTime -> GeneralLedgerAccount)
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
"object")) Parser (Maybe JsonDateTime -> GeneralLedgerAccount)
-> Parser (Maybe JsonDateTime) -> Parser GeneralLedgerAccount
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 JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"updated_at"))
mkGeneralLedgerAccount :: GeneralLedgerAccount
mkGeneralLedgerAccount :: GeneralLedgerAccount
mkGeneralLedgerAccount =
GeneralLedgerAccount
{ generalLedgerAccountAccount_type :: Maybe GeneralLedgerAccountAccount_type
generalLedgerAccountAccount_type = Maybe GeneralLedgerAccountAccount_type
forall a. Maybe a
GHC.Maybe.Nothing
, generalLedgerAccountCode :: Maybe Text
generalLedgerAccountCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, generalLedgerAccountCreated_at :: Maybe JsonDateTime
generalLedgerAccountCreated_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, generalLedgerAccountDescription :: Maybe Text
generalLedgerAccountDescription = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, generalLedgerAccountId :: Maybe Text
generalLedgerAccountId = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, generalLedgerAccountObject :: Maybe Text
generalLedgerAccountObject = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, generalLedgerAccountUpdated_at :: Maybe JsonDateTime
generalLedgerAccountUpdated_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
}
data GeneralLedgerAccountAccount_type
=
GeneralLedgerAccountAccount_typeOther Data.Aeson.Types.Internal.Value
|
GeneralLedgerAccountAccount_typeTyped Data.Text.Internal.Text
|
GeneralLedgerAccountAccount_typeEnumLiability
|
GeneralLedgerAccountAccount_typeEnumRevenue
deriving (Int -> GeneralLedgerAccountAccount_type -> ShowS
[GeneralLedgerAccountAccount_type] -> ShowS
GeneralLedgerAccountAccount_type -> String
(Int -> GeneralLedgerAccountAccount_type -> ShowS)
-> (GeneralLedgerAccountAccount_type -> String)
-> ([GeneralLedgerAccountAccount_type] -> ShowS)
-> Show GeneralLedgerAccountAccount_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GeneralLedgerAccountAccount_type -> ShowS
showsPrec :: Int -> GeneralLedgerAccountAccount_type -> ShowS
$cshow :: GeneralLedgerAccountAccount_type -> String
show :: GeneralLedgerAccountAccount_type -> String
$cshowList :: [GeneralLedgerAccountAccount_type] -> ShowS
showList :: [GeneralLedgerAccountAccount_type] -> ShowS
GHC.Show.Show, GeneralLedgerAccountAccount_type
-> GeneralLedgerAccountAccount_type -> Bool
(GeneralLedgerAccountAccount_type
-> GeneralLedgerAccountAccount_type -> Bool)
-> (GeneralLedgerAccountAccount_type
-> GeneralLedgerAccountAccount_type -> Bool)
-> Eq GeneralLedgerAccountAccount_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GeneralLedgerAccountAccount_type
-> GeneralLedgerAccountAccount_type -> Bool
== :: GeneralLedgerAccountAccount_type
-> GeneralLedgerAccountAccount_type -> Bool
$c/= :: GeneralLedgerAccountAccount_type
-> GeneralLedgerAccountAccount_type -> Bool
/= :: GeneralLedgerAccountAccount_type
-> GeneralLedgerAccountAccount_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON GeneralLedgerAccountAccount_type where
toJSON :: GeneralLedgerAccountAccount_type -> Value
toJSON (GeneralLedgerAccountAccount_typeOther Value
val) = Value
val
toJSON (GeneralLedgerAccountAccount_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (GeneralLedgerAccountAccount_type
GeneralLedgerAccountAccount_typeEnumLiability) = Value
"liability"
toJSON (GeneralLedgerAccountAccount_type
GeneralLedgerAccountAccount_typeEnumRevenue) = Value
"revenue"
instance Data.Aeson.Types.FromJSON.FromJSON GeneralLedgerAccountAccount_type where
parseJSON :: Value -> Parser GeneralLedgerAccountAccount_type
parseJSON Value
val =
GeneralLedgerAccountAccount_type
-> Parser GeneralLedgerAccountAccount_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
"liability" -> GeneralLedgerAccountAccount_type
GeneralLedgerAccountAccount_typeEnumLiability
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"revenue" -> GeneralLedgerAccountAccount_type
GeneralLedgerAccountAccount_typeEnumRevenue
| Bool
GHC.Base.otherwise -> Value -> GeneralLedgerAccountAccount_type
GeneralLedgerAccountAccount_typeOther Value
val
)