haspara-0.0.0.8: A library providing definitions to work with monetary values.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Haspara.Accounting.Account

Description

This module provides definitions for acccounts and types of accounts as they are used in accounting reporting.

Synopsis

Account Kind

data AccountKind Source #

Type encoding for ledger account type.

This type covers both balance sheet and income statement account types:

  1. For balance sheet accounts:
  2. Asset (AccountKindAsset)
  3. Liability (AccountKindLiability)
  4. Equity (AccountKindEquity)
  5. For income statement accounts:
  6. Revenue (AccountKindRevenue)
  7. Expense (AccountKindExpense)

FromJSON and ToJSON instances, too:

>>> :set -XTypeApplications
>>> Data.Aeson.decode @AccountKind "\"ASSET\""
Just AccountKindAsset
>>> Data.Aeson.decode @AccountKind "\"LIABILITY\""
Just AccountKindLiability
>>> Data.Aeson.decode @AccountKind "\"EQUITY\""
Just AccountKindEquity
>>> Data.Aeson.decode @AccountKind "\"REVENUE\""
Just AccountKindRevenue
>>> Data.Aeson.decode @AccountKind "\"EXPENSE\""
Just AccountKindExpense
>>> Data.Aeson.encode AccountKindAsset
"\"ASSET\""
>>> Data.Aeson.encode AccountKindLiability
"\"LIABILITY\""
>>> Data.Aeson.encode AccountKindEquity
"\"EQUITY\""
>>> Data.Aeson.encode AccountKindRevenue
"\"REVENUE\""
>>> Data.Aeson.encode AccountKindExpense
"\"EXPENSE\""

Instances

Instances details
FromJSON AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

ToJSON AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

Bounded AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

Enum AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

Generic AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

Associated Types

type Rep AccountKind :: Type -> Type #

Show AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

Eq AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

Ord AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

Hashable AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

type Rep AccountKind Source # 
Instance details

Defined in Haspara.Accounting.Account

type Rep AccountKind = D1 ('MetaData "AccountKind" "Haspara.Accounting.Account" "haspara-0.0.0.8-83lIPqySeX32MZXT98KoZ2" 'False) ((C1 ('MetaCons "AccountKindAsset" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccountKindLiability" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AccountKindEquity" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AccountKindRevenue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccountKindExpense" 'PrefixI 'False) (U1 :: Type -> Type))))

accountKindText :: AccountKind -> Text Source #

Provides textual representation of a given AccountKind.

>>> accountKindText AccountKindAsset
"Asset"
>>> accountKindText AccountKindLiability
"Liability"
>>> accountKindText AccountKindEquity
"Equity"
>>> accountKindText AccountKindRevenue
"Revenue"
>>> accountKindText AccountKindExpense
"Expense"

Account

data Account o Source #

Type encoding for account values.

This definition provides both the AccountKind and an arbitrary object identifying the account. This arbitrary nature provides flexibility to use-site to use its own account identity and accompanying information when required.

>>> :set -XTypeApplications
>>> let acc = Account AccountKindAsset (1 ::Int)
>>> Data.Aeson.encode acc
"{\"kind\":\"ASSET\",\"object\":1}"
>>> Data.Aeson.decode @(Account Int) (Data.Aeson.encode acc)
Just (Account {accountKind = AccountKindAsset, accountObject = 1})
>>> Data.Aeson.decode (Data.Aeson.encode acc) == Just acc
True

Constructors

Account 

Instances

Instances details
FromJSON o => FromJSON (Account o) Source # 
Instance details

Defined in Haspara.Accounting.Account

ToJSON o => ToJSON (Account o) Source # 
Instance details

Defined in Haspara.Accounting.Account

Generic (Account o) Source # 
Instance details

Defined in Haspara.Accounting.Account

Associated Types

type Rep (Account o) :: Type -> Type #

Methods

from :: Account o -> Rep (Account o) x #

to :: Rep (Account o) x -> Account o #

Show o => Show (Account o) Source # 
Instance details

Defined in Haspara.Accounting.Account

Methods

showsPrec :: Int -> Account o -> ShowS #

show :: Account o -> String #

showList :: [Account o] -> ShowS #

Eq o => Eq (Account o) Source # 
Instance details

Defined in Haspara.Accounting.Account

Methods

(==) :: Account o -> Account o -> Bool #

(/=) :: Account o -> Account o -> Bool #

Ord o => Ord (Account o) Source # 
Instance details

Defined in Haspara.Accounting.Account

Methods

compare :: Account o -> Account o -> Ordering #

(<) :: Account o -> Account o -> Bool #

(<=) :: Account o -> Account o -> Bool #

(>) :: Account o -> Account o -> Bool #

(>=) :: Account o -> Account o -> Bool #

max :: Account o -> Account o -> Account o #

min :: Account o -> Account o -> Account o #

Hashable o => Hashable (Account o) Source # 
Instance details

Defined in Haspara.Accounting.Account

Methods

hashWithSalt :: Int -> Account o -> Int #

hash :: Account o -> Int #

type Rep (Account o) Source # 
Instance details

Defined in Haspara.Accounting.Account

type Rep (Account o) = D1 ('MetaData "Account" "Haspara.Accounting.Account" "haspara-0.0.0.8-83lIPqySeX32MZXT98KoZ2" 'False) (C1 ('MetaCons "Account" 'PrefixI 'True) (S1 ('MetaSel ('Just "accountKind") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AccountKind) :*: S1 ('MetaSel ('Just "accountObject") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 o)))