module HAX.Bookkeeping
(AccountNumber
, Acc
, AccPair
, AccountName(AccountN)
, AccountingRW
, AccountingReadOnly
, AccountsMap
, AmountA
, AmountRW
, AssetName(..)
, BalancingTx(..)
, EntityName
, Environment(..)
, FixedLedger(..)
, FullLedger(..)
, LedgerBounds
, FullAccountName(..)
, Ledger(..)
, LogEntry(..)
, EntityLogEntry
, Posting
, Tx(tPostings,tComment)
, Transfer
, balancesSince
, closingTx
, balanceAt
, logMsg
, singleResult
, singleLog
, curDate
, currentBalance
, fixed
, fromTo
, fromToLimit
, haben
, onceAt
, atYearEnd
, sortedAccountNames
, onceEvery
, onlyAfter
, schedule
, soll
, transferAll
, tx
, logLedger
) where
import HAX.Bookkeeping.Internal
import Control.Monad.Reader
import Data.Array
import HAX.Common
tx :: BalancingTx-> AccountingRW s ()
tx balancingTx = do
UNSAFE_Ledger bals txns <- reader eLedger
date <- reader eDate
name <- reader (fromMaybe "" . eName)
balancedTx <- balanceTx balancingTx
lift $ updateArray txns date ((name,LTx balancedTx):)
mapM_ uNSAFE_addToBalance $ tPostings balancedTx
closingTx :: [AccountName] -> BalancingTx -> AccountingRW s ()
closingTx accs btx = do
postings <- forM accs $ \acc -> (,) acc . negate <$> currentBalance acc
tx $ btx{txPostings = txPostings btx ++ postings}
type Transfer s = String -> AccountName -> AccountName -> AccountingRW s ()
fromTo ::Amount -> Transfer s
fromTo amount comment from to = do
tx $ BalancingTx comment to $ [(from,negate amount)]
fromToLimit :: Amount -> Transfer s
fromToLimit amount comment from to = do
am <- op <$> currentBalance from
fromTo am comment from to
where op = if amount > 0 then min amount else max amount
transferAll :: Transfer s
transferAll comment from to = do am <- currentBalance from
fromTo am comment from to
currentBalance :: AccPair l w => AccountName -> Acc s l w Amount
currentBalance name = fst <$> readEntryForName name
soll :: AccPair l w => AccountName -> Acc s l w Amount
soll = currentBalance
haben :: AccPair l w => AccountName -> Acc s l w Amount
haben = fmap negate . soll
balanceAt :: AccPair l w => ADate -> AccountName -> Acc s l w Amount
balanceAt d = uNSAFE_at d . currentBalance
balancesSince :: AccPair l w => ADate -> AccountName -> Acc s l w [Amount]
balancesSince since acc = do
date <- reader eDate
acc' <- accountNumber acc
start <- fst <$> timeInterval
lift . lAccountHistory (max since start,date) (\t -> (t,acc'))
=<< reader eLedger
curDate :: Monoid w => Acc s l w ADate
curDate = reader eDate
onceAt :: Monoid w => ADate -> Acc s l w () -> Acc s l w ()
onceAt d a = do {d2 <- curDate ; when (d == d2) a }
onceEvery :: Monoid w => ASpan
-> ADate
-> Acc s l w a -> Acc s l w ()
onceEvery period offset action = do { date <- curDate ;
when (period `divides` (dateSpan offset date)) $ action >> return () }
atYearEnd :: Monoid w => Acc s l w a -> Acc s l w ()
atYearEnd = onceEvery 12 (month 12)
onlyAfter :: Monoid w => ADate -> Acc s l w a -> Acc s l w ()
onlyAfter start action = do { date <- curDate ;
when (date > start) $ action >> return () }
schedule :: Monoid w => ADate -> Acc s l w a -> Acc s l w a
schedule date action =do
cdate <- curDate
if (date < cdate ) then
error $ printf
"cannot schedule in the past. \"%v\" lies before today \"%v\""
date cdate
else uNSAFE_at date action
logMsg :: Bool
-> String -> AccountingRW s ()
logMsg toStdout s = do
txns <- reader $ lUNSAFE_LogEntries . eLedger
name <- reader (fromMaybe "" . eName)
date <- reader eDate
let pair = if toStdout then show (date,name)
else name
entry = printf ("(%s) "++s++"\n") pair
lift $ if toStdout
then putStrLn entry
else updateArray txns date ((name,LComment s):)
logLedger :: String -> AccountingRW s ()
logLedger = logMsg False
singleLog :: PrintfArg t => String
-> t
-> AccountingReadOnly body ()
singleLog a b = tell $ logLedger $ printf a b
singleResult :: (PrintfArg a, Num a, Eq a) => String
-> AccountingReadOnly body a
-> AccountingReadOnly body a
singleResult name action = do value <- action
when (value /=0 ) $ singleLog (name++": %v\n") value
return value