haspara-0.0.0.1: A library providing definitions to work with monetary values.
Safe HaskellNone
LanguageHaskell2010

Haspara.Accounting

Synopsis

Documentation

data Account o Source #

Account model.

>>> import Haspara.Accounting.AccountKind (AccountKind(..))
>>> import qualified Data.Aeson as Aeson
>>> let acc = Account AccountKindAsset (1 ::Int)
>>> Aeson.encode acc
"{\"kind\":\"ASSET\",\"object\":1}"
>>> Aeson.decode (Aeson.encode acc) :: Maybe (Account Int)
Just (Account {accountKind = AccountKindAsset, accountObject = 1})
>>> Aeson.decode (Aeson.encode acc) == Just acc
True

Constructors

Account 

Instances

Instances details
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 #

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 #

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 #

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

Defined in Haspara.Accounting.Account

Methods

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

hash :: Account o -> Int #

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

Defined in Haspara.Accounting.Account

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

Defined in Haspara.Accounting.Account

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.1-GIZpgp6So3jGG6B29GnUaf" 'False) (C1 ('MetaCons "Account" 'PrefixI 'True) (S1 ('MetaSel ('Just "accountKind") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AccountKind) :*: S1 ('MetaSel ('Just "accountObject") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 o)))

data AccountKind Source #

Instances

Instances details
Enum AccountKind Source # 
Instance details

Defined in Haspara.Accounting.AccountKind

Eq AccountKind Source # 
Instance details

Defined in Haspara.Accounting.AccountKind

Ord AccountKind Source # 
Instance details

Defined in Haspara.Accounting.AccountKind

Show AccountKind Source # 
Instance details

Defined in Haspara.Accounting.AccountKind

Generic AccountKind Source # 
Instance details

Defined in Haspara.Accounting.AccountKind

Associated Types

type Rep AccountKind :: Type -> Type #

Hashable AccountKind Source # 
Instance details

Defined in Haspara.Accounting.AccountKind

ToJSON AccountKind Source #

ToJSON instance for AccountKind.

>>> Aeson.encode AccountKindAsset
"\"ASSET\""
>>> Aeson.encode AccountKindLiability
"\"LIABILITY\""
>>> Aeson.encode AccountKindEquity
"\"EQUITY\""
>>> Aeson.encode AccountKindRevenue
"\"REVENUE\""
>>> Aeson.encode AccountKindExpense
"\"EXPENSE\""
Instance details

Defined in Haspara.Accounting.AccountKind

FromJSON AccountKind Source #

FromJSON instance for AccountKind.

>>> Aeson.decode "\"Asset\"" :: Maybe AccountKind
Just AccountKindAsset
>>> Aeson.decode "\"aSSET\"" :: Maybe AccountKind
Just AccountKindAsset
>>> Aeson.decode "\"ASSET\"" :: Maybe AccountKind
Just AccountKindAsset
>>> Aeson.decode "\"LIABILITY\"" :: Maybe AccountKind
Just AccountKindLiability
>>> Aeson.decode "\"EQUITY\"" :: Maybe AccountKind
Just AccountKindEquity
>>> Aeson.decode "\"REVENUE\"" :: Maybe AccountKind
Just AccountKindRevenue
>>> Aeson.decode "\"EXPENSE\"" :: Maybe AccountKind
Just AccountKindExpense
Instance details

Defined in Haspara.Accounting.AccountKind

type Rep AccountKind Source # 
Instance details

Defined in Haspara.Accounting.AccountKind

type Rep AccountKind = D1 ('MetaData "AccountKind" "Haspara.Accounting.AccountKind" "haspara-0.0.0.1-GIZpgp6So3jGG6B29GnUaf" '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))))

data Entry o (s :: Nat) Source #

Encoding of a posting entry.

>>> :set -XDataKinds
>>> import Refined
>>> let date = read "2021-01-01"
>>> let oid = 1 :: Int
>>> let qty = $$(refineTH 42) :: UnsignedQuantity 2
>>> let entry = EntryDebit date oid qty
>>> let json = Aeson.encode entry
>>> json
"{\"qty\":42.0,\"obj\":1,\"date\":\"2021-01-01\",\"type\":\"DEBIT\"}"
>>> Aeson.decode json :: Maybe (Entry Int 2)
Just (EntryDebit 2021-01-01 1 (Refined 42.00))
>>> Aeson.decode json == Just entry
True

Instances

Instances details
Eq o => Eq (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Entry

Methods

(==) :: Entry o s -> Entry o s -> Bool #

(/=) :: Entry o s -> Entry o s -> Bool #

Ord o => Ord (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Entry

Methods

compare :: Entry o s -> Entry o s -> Ordering #

(<) :: Entry o s -> Entry o s -> Bool #

(<=) :: Entry o s -> Entry o s -> Bool #

(>) :: Entry o s -> Entry o s -> Bool #

(>=) :: Entry o s -> Entry o s -> Bool #

max :: Entry o s -> Entry o s -> Entry o s #

min :: Entry o s -> Entry o s -> Entry o s #

(Show o, KnownNat s) => Show (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Entry

Methods

showsPrec :: Int -> Entry o s -> ShowS #

show :: Entry o s -> String #

showList :: [Entry o s] -> ShowS #

(ToJSON o, KnownNat s) => ToJSON (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Entry

Methods

toJSON :: Entry o s -> Value #

toEncoding :: Entry o s -> Encoding #

toJSONList :: [Entry o s] -> Value #

toEncodingList :: [Entry o s] -> Encoding #

(FromJSON o, KnownNat s) => FromJSON (Entry o s) Source # 
Instance details

Defined in Haspara.Accounting.Entry

Methods

parseJSON :: Value -> Parser (Entry o s) #

parseJSONList :: Value -> Parser [Entry o s] #

buildEntry :: KnownNat s => Event o s -> AccountKind -> Entry o s Source #

Kind of accountDebitCredit
AssetIncreaseDecrease
LiabilityDecreaseIncrease
Equity/CapitalDecreaseIncrease
Income/RevenueDecreaseIncrease
ExpenseCostDividendIncreaseDecrease

data Event o (s :: Nat) Source #

Encoding of an increment/decrement event.

>>> :set -XDataKinds
>>> import Refined
>>> let date = read "2021-01-01"
>>> let oid = 1 :: Int
>>> let qty = $$(refineTH 42) :: UnsignedQuantity 2
>>> let event = EventDecrement date oid qty
>>> let json = Aeson.encode event
>>> json
"{\"qty\":42.0,\"obj\":1,\"date\":\"2021-01-01\",\"type\":\"DECREMENT\"}"
>>> Aeson.decode json :: Maybe (Event Int 2)
Just (EventDecrement 2021-01-01 1 (Refined 42.00))
>>> Aeson.decode json == Just event
True

Instances

Instances details
Eq o => Eq (Event o s) Source # 
Instance details

Defined in Haspara.Accounting.Event

Methods

(==) :: Event o s -> Event o s -> Bool #

(/=) :: Event o s -> Event o s -> Bool #

Ord o => Ord (Event o s) Source # 
Instance details

Defined in Haspara.Accounting.Event

Methods

compare :: Event o s -> Event o s -> Ordering #

(<) :: Event o s -> Event o s -> Bool #

(<=) :: Event o s -> Event o s -> Bool #

(>) :: Event o s -> Event o s -> Bool #

(>=) :: Event o s -> Event o s -> Bool #

max :: Event o s -> Event o s -> Event o s #

min :: Event o s -> Event o s -> Event o s #

(Show o, KnownNat s) => Show (Event o s) Source # 
Instance details

Defined in Haspara.Accounting.Event

Methods

showsPrec :: Int -> Event o s -> ShowS #

show :: Event o s -> String #

showList :: [Event o s] -> ShowS #

(ToJSON o, KnownNat s) => ToJSON (Event o s) Source # 
Instance details

Defined in Haspara.Accounting.Event

Methods

toJSON :: Event o s -> Value #

toEncoding :: Event o s -> Encoding #

toJSONList :: [Event o s] -> Value #

toEncodingList :: [Event o s] -> Encoding #

(FromJSON o, KnownNat s) => FromJSON (Event o s) Source # 
Instance details

Defined in Haspara.Accounting.Event

Methods

parseJSON :: Value -> Parser (Event o s) #

parseJSONList :: Value -> Parser [Event o s] #

eventObject :: KnownNat s => Event o s -> o Source #

negateEvent :: KnownNat s => Event o s -> Event o s Source #

mkEvent :: (MonadError String m, KnownNat s) => Date -> o -> Quantity s -> m (Event o s) Source #

newtype Posting a o (s :: Nat) Source #

Type encoding for a posting.

>>> :set -XDataKinds
>>> import Haspara.Accounting
>>> import Refined
>>> import qualified Data.Aeson as Aeson
>>> import qualified Data.List.NonEmpty as NE
>>> let date = read "2021-01-01"
>>> let oid = 1 :: Int
>>> let qty = $$(refineTH 42) :: UnsignedQuantity 2
>>> let event = EventDecrement date oid qty
>>> let account = Account AccountKindAsset ("Cash" :: String, 1 ::Int)
>>> let posting =  Posting . NE.fromList $ [(event, account)]
>>> let json = Aeson.encode posting
>>> json
"[[{\"qty\":42.0,\"obj\":1,\"date\":\"2021-01-01\",\"type\":\"DECREMENT\"},{\"kind\":\"ASSET\",\"object\":[\"Cash\",1]}]]"
>>> Aeson.decode json :: Maybe (Posting (String, Int) Int 2)
Just (Posting ((EventDecrement 2021-01-01 1 (Refined 42.00),Account {accountKind = AccountKindAsset, accountObject = ("Cash",1)}) :| []))
>>> Aeson.decode json == Just posting
True

Constructors

Posting (NonEmpty (Event o s, Account a)) 

Instances

Instances details
(Eq o, Eq a) => Eq (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Posting

Methods

(==) :: Posting a o s -> Posting a o s -> Bool #

(/=) :: Posting a o s -> Posting a o s -> Bool #

(Ord o, Ord a) => Ord (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Posting

Methods

compare :: Posting a o s -> Posting a o s -> Ordering #

(<) :: Posting a o s -> Posting a o s -> Bool #

(<=) :: Posting a o s -> Posting a o s -> Bool #

(>) :: Posting a o s -> Posting a o s -> Bool #

(>=) :: Posting a o s -> Posting a o s -> Bool #

max :: Posting a o s -> Posting a o s -> Posting a o s #

min :: Posting a o s -> Posting a o s -> Posting a o s #

(KnownNat s, Show o, Show a) => Show (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Posting

Methods

showsPrec :: Int -> Posting a o s -> ShowS #

show :: Posting a o s -> String #

showList :: [Posting a o s] -> ShowS #

Generic (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Posting

Associated Types

type Rep (Posting a o s) :: Type -> Type #

Methods

from :: Posting a o s -> Rep (Posting a o s) x #

to :: Rep (Posting a o s) x -> Posting a o s #

(ToJSON a, ToJSON o, KnownNat s) => ToJSON (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Posting

Methods

toJSON :: Posting a o s -> Value #

toEncoding :: Posting a o s -> Encoding #

toJSONList :: [Posting a o s] -> Value #

toEncodingList :: [Posting a o s] -> Encoding #

(KnownNat s, FromJSON o, FromJSON a) => FromJSON (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Posting

Methods

parseJSON :: Value -> Parser (Posting a o s) #

parseJSONList :: Value -> Parser [Posting a o s] #

type Rep (Posting a o s) Source # 
Instance details

Defined in Haspara.Accounting.Posting

type Rep (Posting a o s) = D1 ('MetaData "Posting" "Haspara.Accounting.Posting" "haspara-0.0.0.1-GIZpgp6So3jGG6B29GnUaf" 'True) (C1 ('MetaCons "Posting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Event o s, Account a)))))

postingEvents :: KnownNat s => Posting a o s -> [o] Source #

post :: KnownNat s => Posting a o s -> [(Account a, Entry o s)] Source #

data Ledger a o (s :: Nat) Source #

Constructors

Ledger 

Instances

Instances details
(Eq a, Eq o) => Eq (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

(==) :: Ledger a o s -> Ledger a o s -> Bool #

(/=) :: Ledger a o s -> Ledger a o s -> Bool #

(Ord a, Ord o) => Ord (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

compare :: Ledger a o s -> Ledger a o s -> Ordering #

(<) :: Ledger a o s -> Ledger a o s -> Bool #

(<=) :: Ledger a o s -> Ledger a o s -> Bool #

(>) :: Ledger a o s -> Ledger a o s -> Bool #

(>=) :: Ledger a o s -> Ledger a o s -> Bool #

max :: Ledger a o s -> Ledger a o s -> Ledger a o s #

min :: Ledger a o s -> Ledger a o s -> Ledger a o s #

(KnownNat s, Show a, Show o) => Show (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

showsPrec :: Int -> Ledger a o s -> ShowS #

show :: Ledger a o s -> String #

showList :: [Ledger a o s] -> ShowS #

Generic (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Associated Types

type Rep (Ledger a o s) :: Type -> Type #

Methods

from :: Ledger a o s -> Rep (Ledger a o s) x #

to :: Rep (Ledger a o s) x -> Ledger a o s #

(ToJSON o, ToJSON a, KnownNat s) => ToJSON (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

toJSON :: Ledger a o s -> Value #

toEncoding :: Ledger a o s -> Encoding #

toJSONList :: [Ledger a o s] -> Value #

toEncodingList :: [Ledger a o s] -> Encoding #

(KnownNat s, FromJSON a, FromJSON o) => FromJSON (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

parseJSON :: Value -> Parser (Ledger a o s) #

parseJSONList :: Value -> Parser [Ledger a o s] #

type Rep (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (Ledger a o s) = D1 ('MetaData "Ledger" "Haspara.Accounting.Ledger" "haspara-0.0.0.1-GIZpgp6So3jGG6B29GnUaf" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ledgerAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Account a)) :*: S1 ('MetaSel ('Just "ledgerOpening") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s))) :*: (S1 ('MetaSel ('Just "ledgerClosing") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s)) :*: S1 ('MetaSel ('Just "ledgerRunning") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [LedgerItem o s]))))

data LedgerItem o (s :: Nat) Source #

Constructors

LedgerItem 

Fields

Instances

Instances details
Eq o => Eq (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

(==) :: LedgerItem o s -> LedgerItem o s -> Bool #

(/=) :: LedgerItem o s -> LedgerItem o s -> Bool #

Ord o => Ord (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

compare :: LedgerItem o s -> LedgerItem o s -> Ordering #

(<) :: LedgerItem o s -> LedgerItem o s -> Bool #

(<=) :: LedgerItem o s -> LedgerItem o s -> Bool #

(>) :: LedgerItem o s -> LedgerItem o s -> Bool #

(>=) :: LedgerItem o s -> LedgerItem o s -> Bool #

max :: LedgerItem o s -> LedgerItem o s -> LedgerItem o s #

min :: LedgerItem o s -> LedgerItem o s -> LedgerItem o s #

(Show o, KnownNat s) => Show (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

showsPrec :: Int -> LedgerItem o s -> ShowS #

show :: LedgerItem o s -> String #

showList :: [LedgerItem o s] -> ShowS #

Generic (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Associated Types

type Rep (LedgerItem o s) :: Type -> Type #

Methods

from :: LedgerItem o s -> Rep (LedgerItem o s) x #

to :: Rep (LedgerItem o s) x -> LedgerItem o s #

(KnownNat s, ToJSON o) => ToJSON (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

(FromJSON o, KnownNat s) => FromJSON (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (LedgerItem o s) = D1 ('MetaData "LedgerItem" "Haspara.Accounting.Ledger" "haspara-0.0.0.1-GIZpgp6So3jGG6B29GnUaf" 'False) (C1 ('MetaCons "LedgerItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerItemEntry") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Entry o s)) :*: S1 ('MetaSel ('Just "ledgerItemBalance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s))))

mkLedger :: KnownNat s => Account a -> Quantity s -> [Entry o s] -> Ledger a o s Source #

addEntry :: KnownNat s => Ledger a o s -> Entry o s -> Ledger a o s Source #

entryObject :: KnownNat s => Entry o s -> o Source #