hax-0.0.2: Haskell cash-flow and tax simulation

Safe HaskellNone
LanguageHaskell2010

HAX.Bookkeeping.Internal

Contents

Description

This module contains the internal type and functions not to be used directly as most of them are unsafe, meaning that they allow actions that violate double-entry contraints or actions on accounts other than the current body's accounts (via UNSAFE_AccountN).

Therefore, do not use this module directly, use HAX.Bookkeeping instead.

Synopsis

Account Names and Numbers

data FullAccountName Source #

uniquely identifying name used to lookup the account numbers

Constructors

FAN 

data AccountName Source #

this type is used to make functions taking AccountNames polymorphic.

Constructors

AccountN String

account for the current entity. Only these accounts should be accessible in accounting actions

UNSAFE_AccountN FullAccountName

full account for internal use only

type AccountsMap = Map FullAccountName AccountNumber Source #

The map from FullAccountNames to AccountNumbers used internally to address the efficient Ledger array storage

sortedAccountNames :: AccountsMap -> [FullAccountName] Source #

Extract accounts names order by their internal account numbers

Postings and Transactions

data Tx Source #

A transaction that is already balanced. Such an object can only be built from BalancingTx using balanceTx and is never needed as function input. This format is used to log the transactions in the Ledger 's LogEntry.

Constructors

UNSAFE_Tx 

Instances

Show Tx Source # 

Methods

showsPrec :: Int -> Tx -> ShowS #

show :: Tx -> String #

showList :: [Tx] -> ShowS #

Generic Tx Source # 

Associated Types

type Rep Tx :: * -> * #

Methods

from :: Tx -> Rep Tx x #

to :: Rep Tx x -> Tx #

type Rep Tx Source # 
type Rep Tx = D1 (MetaData "Tx" "HAX.Bookkeeping.Internal" "hax-0.0.2-Lj8gOWDiNX5LEcFpshI2lz" False) (C1 (MetaCons "UNSAFE_Tx" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "tComment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Comment)) (S1 (MetaSel (Just Symbol "tPostings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [InternalPosting]))))

data BalancingTx Source #

A transaction involving only accounts relative to a body, and that is self balancing through the use of an account for the remains

balanceTx :: Monoid w => BalancingTx -> Acc s l w Tx Source #

Balance a BalancingTx and prepend the entitiyName to the comment. This is only used internally

The Ledger

data LogEntry Source #

Information that is logged while the ledger is built

Constructors

LTx Tx

Transactions of the current time period

LComment String

Random comment to be put into the ledger

Instances

Show LogEntry Source # 
Generic LogEntry Source # 

Associated Types

type Rep LogEntry :: * -> * #

Methods

from :: LogEntry -> Rep LogEntry x #

to :: Rep LogEntry x -> LogEntry #

type Rep LogEntry Source # 
type Rep LogEntry = D1 (MetaData "LogEntry" "HAX.Bookkeeping.Internal" "hax-0.0.2-Lj8gOWDiNX5LEcFpshI2lz" False) ((:+:) (C1 (MetaCons "LTx" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tx))) (C1 (MetaCons "LComment" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))

class Ledger l where Source #

This class defines what a Ledger is:

Minimal complete definition

lBounds, lReadEntry, lAccountHistory, lFix, lunsafeFix

Methods

lBounds :: l -> IO LedgerBounds Source #

it has bounds

lReadEntry :: LedgerIndex -> l -> IO (Amount, [EntityLogEntry]) Source #

single entries for a given account and date consisting of the account balance and the log entries for that date can be read.

lAccountHistory :: (ADate, ADate) -> (ADate -> LedgerIndex) -> l -> IO [Amount] Source #

the account history can be read

lFix :: l -> IO FixedLedger Source #

it can be fixed into an immutable type

lunsafeFix :: l -> IO FixedLedger Source #

fix withou making a copy. This is has to be safe to use, if the mutable version is never modified after the freeze operation.

data LedgerRW Source #

LedgerRW implements a writable (within the IO monad) Ledger.

The total balance is always zero and no transactions that depend on future values are allowed. This is guaranteed, by not exporting UNSAFE_Ledger and instead, the ledger is only changed using the exported safe functions. E.g. tx, fromTo, ...

Constructors

UNSAFE_Ledger 

Fields

data FixedLedger Source #

This type implements the Ledger in immutable form, suitable as the main result of the whole program or for accounting accounts that are garantueed to not change the ledger.

Accounting Environment

data Environment body ledger Source #

Represents the environment an accounting action is run on.

Constructors

Env 

Fields

Instances

Monoid w => Eq (AmountA s l w) Source # 

Methods

(==) :: AmountA s l w -> AmountA s l w -> Bool #

(/=) :: AmountA s l w -> AmountA s l w -> Bool #

Monoid w => Fractional (AmountA s l w) Source # 

Methods

(/) :: AmountA s l w -> AmountA s l w -> AmountA s l w #

recip :: AmountA s l w -> AmountA s l w #

fromRational :: Rational -> AmountA s l w #

Monoid w => Num (AmountA s l w) Source #

Allows to use +,-,*,negate directly on actions that return an amount. Furthermore any numeral can be used directly as (trivial) accounting action:

soll "Cash" + 4 :: AmountA s l

Methods

(+) :: AmountA s l w -> AmountA s l w -> AmountA s l w #

(-) :: AmountA s l w -> AmountA s l w -> AmountA s l w #

(*) :: AmountA s l w -> AmountA s l w -> AmountA s l w #

negate :: AmountA s l w -> AmountA s l w #

abs :: AmountA s l w -> AmountA s l w #

signum :: AmountA s l w -> AmountA s l w #

fromInteger :: Integer -> AmountA s l w #

Monoid w => Ord (AmountA s l w) Source #

Allows to use min and max and its derivaties directly on actions that return an amount:

min ( "Cash") (balanceAt date "Cash") :: AmountA s l

Methods

compare :: AmountA s l w -> AmountA s l w -> Ordering #

(<) :: AmountA s l w -> AmountA s l w -> Bool #

(<=) :: AmountA s l w -> AmountA s l w -> Bool #

(>) :: AmountA s l w -> AmountA s l w -> Bool #

(>=) :: AmountA s l w -> AmountA s l w -> Bool #

max :: AmountA s l w -> AmountA s l w -> AmountA s l w #

min :: AmountA s l w -> AmountA s l w -> AmountA s l w #

Accounting Actions

type Acc body ledger writer = RWST (Environment body ledger) writer () IO Source #

The Accounting Monad

This monad is a stack of Reader Writer and IO monad.

Actions from this monad can read an immutable environment. This environment however, contains references to mutable arrays (see LedgerRW), which can be modified through IO actions lifted into this monad into this monad.

The body type variable will contain the type of the Body the current accounting action is concerned with.

type AccountingRW body = Acc body LedgerRW () Source #

A specializations for read-write accounting actions with no (i.e. trivial '()') writer output

type AccountingReadOnly body = Acc body FixedLedger (AccountingRW body ()) Source #

A specialization for read-only actions. These actions can however produce read-write actions as output via the Writer Monad. This is used in fixed.

class (Monoid w, Ledger l) => AccPair l w Source #

Short-cut class used in type signatures involving Acc and its derivatives

Instances

(Monoid w, Ledger l) => AccPair l w Source # 

type AmountRW body = AccountingRW body Amount Source #

type synonym for an accounting action that has an amount as result

type AmountA body l w = Acc body l w Amount Source #

fixed :: AccountingReadOnly s a -> AccountingRW s a Source #

run a read only action and its genrated read-write output within a general accounting action and pass on its result.

Internal Helper Functions

nameErr :: MonadReader (Environment body ledger) m => [Char] -> m EntityName Source #

Tries to get the eName of the current entity and throws an error if it is Nothing.

Internal UNSAFE Functions

uNSAFE_at :: Monoid w => ADate -> Acc s l w a -> Acc s l w a Source #

perform an accounting action at any date

uNSAFE_carryOver :: AccountingRW s () Source #

add last month's balances to previous month's. This is performed once for every time step in generate

Orphan instances

Monad m => Monoid (m ()) Source # 

Methods

mempty :: m () #

mappend :: m () -> m () -> m () #

mconcat :: [m ()] -> m () #