module HAX.Bookkeeping.Internal where
import HAX.Common
import Control.Monad.RWS.Strict
import Data.Array
import Data.Array.Unsafe
import Data.Functor.Compose
import qualified Data.Map as M
import GHC.Generics
type AccountNumber = Int
type AssetName = String
type EntityName = String
data FullAccountName = FAN
{ fEntity :: EntityName
, fAccount :: String
}
deriving (Eq, Ord,Show, Generic)
swapFAN :: FullAccountName -> FullAccountName
swapFAN (FAN a b) = FAN b a
data AccountName = AccountN String
| UNSAFE_AccountN FullAccountName
deriving (Eq, Ord,Show)
instance PrintfArg AccountName where
formatArg (AccountN s) = formatString s
formatArg (UNSAFE_AccountN _) = error "not implemented: formatArg (UNSAFE_AccountN)"
instance IsString AccountName where
fromString = AccountN
type AccountsMap = M.Map FullAccountName AccountNumber
sortedAccountNames :: AccountsMap -> [FullAccountName]
sortedAccountNames = fmap fst . sortBy (comparing snd) . M.toList
internalAccountNumber :: FullAccountName -> AccountsMap -> AccountNumber
internalAccountNumber name accs = fromMaybe (error $
printf "Account '%s' not found\nAvailable Accounts:\n%s"
(show name) $ unlines $ show <$> M.toList accs)
$ M.lookup name accs
type Posting = (AccountName,Amount)
type InternalPosting = (AccountNumber,Amount)
data Tx = UNSAFE_Tx { tComment :: Comment
, tPostings :: [InternalPosting]
}
deriving (Show,Generic)
data BalancingTx = BalancingTx { txComment :: Comment
, txRemains :: AccountName
, txPostings :: [Posting]
}
balanceTx :: (Monoid w) => BalancingTx -> Acc s l w Tx
balanceTx (BalancingTx comment remains postings) = do
name <- nameErr "Transactions are only allowed in the presence of an entity"
fmap (UNSAFE_Tx $ printf "(%s) %s" name comment) $
mapM (\(name,amount) -> do number <- accountNumber name
return (number,amount) )
$ (remains,negate $ sum $ snd <$> postings):postings
data LogEntry = LTx Tx
| LComment String
deriving (Generic,Show)
type EntityLogEntry = (EntityName,LogEntry)
type LedgerIndex = (ADate,AccountNumber)
type LedgerBounds = (LedgerIndex, LedgerIndex)
class Ledger l where
lBounds :: l -> IO LedgerBounds
lReadEntry :: LedgerIndex -> l -> IO (Amount,[EntityLogEntry])
lAccountHistory :: (ADate,ADate) -> (ADate -> LedgerIndex) -> l -> IO [Amount]
lFix :: l -> IO FixedLedger
lunsafeFix :: l -> IO FixedLedger
data LedgerRW = UNSAFE_Ledger
{ lUNSAFE_Bals :: IOArray LedgerIndex Amount
, lUNSAFE_LogEntries :: IOArray ADate [EntityLogEntry]
}
data FixedLedger = FixedLedger
{ lBals :: Array LedgerIndex Amount
, lLogEntries :: Array ADate [EntityLogEntry]
}
data FullLedger = FullLedger
{ flLedger :: FixedLedger
, flAccounts :: AccountsMap
}
instance Ledger LedgerRW where
lBounds (UNSAFE_Ledger ledger _) = getBounds ledger
lReadEntry (date,acc) (UNSAFE_Ledger bals txns) =
liftM2 (,) (readArray bals (date,acc)) $ readArray txns date
lAccountHistory times f (UNSAFE_Ledger bals _) =
getElems =<< mapIndices times f bals
lFix (UNSAFE_Ledger bals txns) = liftM2 FixedLedger (freeze bals) $ freeze txns
lunsafeFix (UNSAFE_Ledger bals txns) = liftM2 FixedLedger (unsafeFreeze bals) $ unsafeFreeze txns
instance Ledger FixedLedger where
lBounds (FixedLedger ledger _) = return $ bounds ledger
lReadEntry (date,acc) (FixedLedger bals txns) =
return (bals ! (date,acc), txns ! date)
lAccountHistory times f (FixedLedger bals _) =
return $ elems $ ixmap times f bals
lFix = return
lunsafeFix = return
data Environment body ledger = Env {
eLedger :: ledger
, eAccounts :: AccountsMap
, eDate :: ADate
, eBody :: body
, eName :: Maybe EntityName
}
type Acc body ledger writer = RWST (Environment body ledger) writer () IO
type AccountingRW body = Acc body LedgerRW ()
type AccountingReadOnly body = Acc body FixedLedger (AccountingRW body ())
instance Monad m => Monoid (m ()) where
mappend = (>>)
mempty = return ()
class (Monoid w, Ledger l) => AccPair l w where
instance (Monoid w, Ledger l) => AccPair l w where
type AmountRW body = AccountingRW body Amount
type AmountA body l w = Acc body l w Amount
fixed :: AccountingReadOnly s a -> AccountingRW s a
fixed actionRO = do e <- ask
l' <- lift . lFix $ eLedger e
(res,actionRW) <- lift $ evalRWST actionRO e{eLedger = l'} ()
actionRW
return res
instance Monoid w => Eq (AmountA s l w) where
(==) = error "Eq (AmountA s l) is impossible"
instance Monoid w => Ord (AmountA s l w) where
min = liftM2 min
max = liftM2 max
(<=) = error "(<=) for (AmountA s l) is impossible"
instance Monoid w => Num (AmountA s l w) where
(*) = liftM2 (*)
(+) = liftM2 (+)
() = liftM2 ()
negate = fmap negate
abs = fmap abs
signum = fmap signum
fromInteger = return . fromInteger
instance Monoid w => Fractional (AmountA s l w) where
(/) = liftM2 (/)
recip = fmap recip
fromRational = return . fromRational
ledgerBounds :: (Monoid w, Ledger l) => Acc s l w (LedgerIndex, LedgerIndex)
ledgerBounds = lift . lBounds =<< reader eLedger
readEntryForNumber :: (Monoid w, Ledger l) => AccountNumber -> Acc s l w (Amount,[EntityLogEntry])
readEntryForNumber acc = do date <- reader eDate
lift . lReadEntry (date,acc) =<< reader eLedger
accountsNumbers :: (Monoid w, Ledger l) => Acc s l w [AccountNumber]
accountsNumbers = range2 <$> ledgerBounds
timeInterval :: (Monoid w, Ledger l) => Acc s l w (ADate,ADate)
timeInterval = both fst <$> ledgerBounds
accountNumber :: Monoid w => AccountName -> Acc s l w AccountNumber
accountNumber (UNSAFE_AccountN acc) = internalAccountNumber acc <$> reader eAccounts
accountNumber (AccountN acc) = do
entName <- reader $ nameErr $ printf "'AccountN %s' is not defined" acc
internalAccountNumber (FAN entName acc) <$> reader eAccounts
nameErr msg = reader (fromMaybe err . eName)
where err = error $ printf
"There is no current entity. "++ msg
readEntryForName :: (Monoid w, Ledger l) => AccountName -> Acc s l w (Amount,[EntityLogEntry])
readEntryForName acc = readEntryForNumber =<< accountNumber acc
uNSAFE_at :: Monoid w => ADate -> Acc s l w a -> Acc s l w a
uNSAFE_at date = local (\e -> e{eDate=date})
uNSAFE_addToBalance :: InternalPosting -> AccountingRW s ()
uNSAFE_addToBalance (acc,amount) = do
UNSAFE_Ledger bals _ <- reader eLedger
date <- reader eDate
lift $ updateArray bals (date,acc) (+amount)
uNSAFE_carryOver :: AccountingRW s ()
uNSAFE_carryOver = do
start <- fst <$> timeInterval
oldD <- reader $ (shift $ 1) . eDate
when (start <= oldD) $ accountsNumbers >>=
(mapM_ $ \ac -> do
oldB <- fst <$> uNSAFE_at oldD (readEntryForNumber ac)
uNSAFE_addToBalance (ac,oldB))