hledger-interest-1.6.0/0000755000000000000000000000000007346545000013154 5ustar0000000000000000hledger-interest-1.6.0/Hledger/0000755000000000000000000000000007346545000014526 5ustar0000000000000000hledger-interest-1.6.0/Hledger/Interest.hs0000644000000000000000000000643307346545000016665 0ustar0000000000000000module Hledger.Interest ( Computer, runComputer , Config(..) , InterestState(..), nullInterestState , processTransaction, computeInterest , module Hledger.Interest.DayCountConvention , module Hledger.Interest.Rate , module Hledger.Data ) where import Hledger.Data import Hledger.Interest.DayCountConvention import Hledger.Interest.Rate import Control.Monad.RWS import Data.Decimal import Data.Maybe import qualified Data.Text as T import Data.Time.Calendar import Data.Time.Calendar.OrdinalDate type Computer = RWS Config [Transaction] InterestState runComputer :: Config -> Computer () -> [Transaction] runComputer cfg f = ts where ((),_,ts) = runRWS f cfg nullInterestState data Config = Config { interestAccount :: AccountName , sourceAccount :: AccountName , targetAccount :: AccountName , dayCountConvention :: DayCountConvention , interestRate :: Rate } data InterestState = InterestState { balancedUntil :: Day , balance :: MixedAmount } nullInterestState :: InterestState nullInterestState = InterestState { balancedUntil = nulldate , balance = nullmixedamt } processTransaction :: Transaction -> Computer () processTransaction ts = do let day = fromMaybe (tdate ts) (tdate2 ts) computeInterest day interestAcc <- asks interestAccount let posts = [ p | p <- tpostings ts, interestAcc == paccount p ] forM_ posts $ \p -> do bal <- gets balance modify (\st -> st { balance = normaliseMixedAmountSquashPricesForDisplay (bal + pamount p) }) computeInterest :: Day -> Computer () computeInterest day = do from <- gets balancedUntil bal <- gets balance rate <- asks interestRate let (endOfPeriod,ratePerAnno) = rate from to = min day endOfPeriod newFrom = succ to modify (\st -> st { balancedUntil = newFrom }) when (to >= from && not (mixedAmountIsZero bal)) $ do diff <- asks dayCountConvention t <- mkTrans to ((from `diff` to) + 1) ratePerAnno tell [t] processTransaction t when (newFrom < day) (computeInterest day) daysInYear :: Day -> Computer Integer daysInYear now = asks dayCountConvention >>= \diff -> return (day1 `diff` day2) where day1 = fromGregorian (fst (toOrdinalDate now)) 1 1 day2 = fromGregorian (succ (fst (toOrdinalDate now))) 1 1 mkTrans :: Day -> Integer -> Decimal -> Computer Transaction mkTrans day days ratePerAnno = do bal <- gets balance srcAcc <- asks sourceAccount targetAcc <- asks targetAccount perDayScalar <- daysInYear day let t = nulltransaction { tdate = day , tdescription = T.pack $ showPercent ratePerAnno ++ " interest for " ++ showMixedAmount bal ++ " over " ++ show days ++ " days" , tpostings = [pTarget,pSource] } pTarget = nullposting { paccount = targetAcc , pamount = Mixed [ a { aquantity = (aquantity a * ratePerAnno) / fromInteger perDayScalar * fromInteger days } | a <- amounts bal ] , ptype = RegularPosting , ptransaction = Just t } pSource = nullposting { paccount = srcAcc , pamount = negate (pamount pTarget) , ptype = RegularPosting , ptransaction = Just t } return t showPercent :: Decimal -> String showPercent r = shows (r * 100) "%" hledger-interest-1.6.0/Hledger/Interest/0000755000000000000000000000000007346545000016323 5ustar0000000000000000hledger-interest-1.6.0/Hledger/Interest/DayCountConvention.hs0000644000000000000000000000306307346545000022452 0ustar0000000000000000module Hledger.Interest.DayCountConvention ( DayCountConvention , diffAct , diff30_360 , diff30E_360 , diff30E_360isda ) where import Control.Exception ( assert ) import Data.Time.Calendar type DayCountConvention = Day -> Day -> Integer diffAct :: DayCountConvention diffAct date1 date2 = assert (date1 <= date2) $ fromInteger (date2 `diffDays` date1) mkDiff30_360 :: (Integer,Int,Int) -> (Integer,Int,Int) -> Integer mkDiff30_360 (y1,m1,d1) (y2,m2,d2) = 360*(y2-y1) + 30*toInteger (m2-m1) + toInteger (d2-d1) -- The un-corrected naked formular. diff30_360 :: DayCountConvention diff30_360 date1 date2 = assert (date1 <= date2) $ mkDiff30_360 (toGregorian date1) (toGregorian date2) -- No month has more than 30 days, but February may have 28 or 29; i.e. -- there are 32 days between 2003-02-28 and 2003-03-31. Commonly known -- as "Deutsche Zinsmethode 30 / 360". diff30E_360 :: DayCountConvention diff30E_360 date1 date2 = assert (date1 <= date2) $ mkDiff30_360 (y1, m1, min 30 d1) (y2, m2, min 30 d2) where (y1,m1,d1) = toGregorian date1 (y2,m2,d2) = toGregorian date2 -- This variant additionally normalizes end-of-months to 30, i.e. there -- are 30 days between 2003-02-28 and 2003-03-31. diff30E_360isda :: DayCountConvention diff30E_360isda date1 date2 = assert (date1 <= date2) $ mkDiff30_360 (y1, m1, d1') (y2, m2, d2') where (y1,m1,d1) = toGregorian date1 (y2,m2,d2) = toGregorian date2 d1' = if d1 > 30 || d1 == gregorianMonthLength y1 m1 then 30 else d1 d2' = if d1 > 30 || d2 == gregorianMonthLength y2 m2 then 30 else d2 hledger-interest-1.6.0/Hledger/Interest/Rate.hs0000644000000000000000000000652607346545000017563 0ustar0000000000000000module Hledger.Interest.Rate ( Rate, perAnno, perAnnoSchedule, constant, bgb288, ingDiba, db24 ) where import Data.Time.Calendar import Data.Time.Calendar.OrdinalDate import Data.Decimal import Data.List (sortOn) type Rate = Day -> (Day,Decimal) constant :: Decimal -> Rate constant rate _ = (day 999999 12 31, rate) perAnno :: Decimal -> Rate perAnno rate date = (yearEnd date, rate) perAnnoSchedule :: [(Day,Decimal)] -> Rate perAnnoSchedule schedule date = (yearEnd date, effectiveRate) where (_, effectiveRate) = last $ takeWhile (\(fromDate, _) -> fromDate Int -> Int -> Day day = fromGregorian yearEnd :: Day -> Day yearEnd date = day (fst (toOrdinalDate date)) 12 31 bgb288 :: Rate bgb288 = basiszins (5/100) basiszins :: Decimal -> Rate basiszins r date = (to, r + p) where (_,to,p) = head (dropWhile (\(_,to',_) -> to' < date) basiszinsTable) basiszinsTable :: [(Day, Day, Decimal)] basiszinsTable = [ (day 2002 01 01, day 2002 06 30, 257 / 10000) , (day 2002 07 01, day 2002 12 31, 247 / 10000) , (day 2003 01 01, day 2003 06 30, 197 / 10000) , (day 2003 07 01, day 2003 12 31, 122 / 10000) , (day 2004 01 01, day 2004 06 30, 114 / 10000) , (day 2004 07 01, day 2004 12 31, 113 / 10000) , (day 2005 01 01, day 2005 06 30, 121 / 10000) , (day 2005 07 01, day 2005 12 31, 117 / 10000) , (day 2006 01 01, day 2006 06 30, 137 / 10000) , (day 2006 07 01, day 2006 12 31, 195 / 10000) , (day 2007 01 01, day 2007 06 30, 270 / 10000) , (day 2007 07 01, day 2007 12 31, 319 / 10000) , (day 2008 01 01, day 2008 06 30, 332 / 10000) , (day 2008 07 01, day 2008 12 31, 319 / 10000) , (day 2009 01 01, day 2009 06 30, 162 / 10000) , (day 2009 07 01, day 2009 12 31, 12 / 10000) , (day 2010 01 01, day 2010 06 30, 12 / 10000) , (day 2010 07 01, day 2010 12 31, 12 / 10000) , (day 2011 01 01, day 2011 06 30, 12 / 10000) , (day 2011 07 01, day 2999 12 31, 37 / 10000) , (day 2011 01 01, day 2011 06 30, 12 / 10000) , (day 2011 07 01, day 2011 12 31, 37 / 10000) , (day 2012 01 01, day 2012 06 30, 12 / 10000) , (day 2012 07 01, day 2012 12 31, 12 / 10000) , (day 2013 01 01, day 2013 06 30, -13 / 10000) , (day 2013 07 01, day 2013 12 31, -38 / 10000) , (day 2014 01 01, day 2014 06 30, -63 / 10000) , (day 2014 07 01, day 2014 12 31, -73 / 10000) , (day 2015 01 01, day 2015 06 30, -83 / 10000) , (day 2015 07 01, day 2015 12 31, -83 / 10000) , (day 2016 01 01, day 2016 06 30, -83 / 10000) , (day 2016 07 01, day 2016 12 31, -88 / 10000) , (day 2017 01 01, day 2017 06 30, -88 / 10000) , (day 2017 07 01, day 2017 12 31, -88 / 10000) , (day 2018 01 01, day 2018 06 30, -88 / 10000) ] ingDiba :: Rate ingDiba date = (to, p) where (_,to,p) = head (dropWhile (\(_,to',_) -> to' < date) ingDibaTable) ingDibaTable :: [(Day, Day, Decimal)] ingDibaTable = [ (day 2009 01 01, day 2009 12 31, 150 / 10000) , (day 2010 01 01, day 2010 12 31, 150 / 10000) , (day 2011 01 01, day 2011 07 14, 150 / 10000) , (day 2011 07 15, day 2999 12 31, 175 / 10000) ] db24 :: Rate db24 date = (to, p) where (_,to,p) = head (dropWhile (\(_,to',_) -> to' < date) db24Table) db24Table :: [(Day, Day, Decimal)] db24Table = [ (day 2000 10 06, day 2010 09 15, 638 / 10000) , (day 2010 09 16, day 2999 12 31, 415 / 10000) ] hledger-interest-1.6.0/LICENSE0000644000000000000000000000300107346545000014153 0ustar0000000000000000Copyright (c) 2011 Peter Simons All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of Peter Simons nor the names of other contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. hledger-interest-1.6.0/Main.hs0000644000000000000000000001426707346545000014406 0ustar0000000000000000module Main ( main ) where import Hledger.Interest import Hledger.Query import Hledger.Read import Hledger.Utils import Control.Exception ( bracket ) import Control.Monad import Data.List ( sortOn ) import Data.Maybe import qualified Data.Text as T import Data.Version import System.Console.GetOpt import System.Environment import System.Exit import System.IO import Paths_hledger_interest ( version ) data Options = Options { optVerbose :: Bool , optShowVersion :: Bool , optShowHelp :: Bool , optInput :: [FilePath] , optSourceAcc :: String , optTargetAcc :: String , optDCC :: Maybe DayCountConvention , optRate :: Maybe Rate , optBalanceToday :: Bool , optIgnoreAssertions :: Bool } defaultOptions :: Options defaultOptions = Options { optVerbose = True , optShowVersion = False , optShowHelp = False , optInput = [] , optSourceAcc = "" , optTargetAcc = "" , optDCC = Nothing , optRate = Nothing , optBalanceToday = False , optIgnoreAssertions = False } options :: [OptDescr (Options -> Options)] options = [ Option ['h'] ["help"] (NoArg (\o -> o { optShowHelp = True })) "print this message and exit" , Option ['V'] ["version"] (NoArg (\o -> o { optShowVersion = True })) "show version number and exit" , Option ['v'] ["verbose"] (NoArg (\o -> o { optVerbose = True })) "echo input ledger to stdout (default)" , Option ['q'] ["quiet"] (NoArg (\o -> o { optVerbose = False })) "don't echo input ledger to stdout" , Option [] ["today"] (NoArg (\o -> o { optBalanceToday = True })) "compute interest up until today" , Option ['f'] ["file"] (ReqArg (\f o -> o { optInput = f : optInput o }) "FILE") "input ledger file (pass '-' for stdin)" , Option ['s'] ["source"] (ReqArg (\a o -> o { optSourceAcc = a }) "ACCOUNT") "interest source account" , Option ['t'] ["target"] (ReqArg (\a o -> o { optTargetAcc = a }) "ACCOUNT") "interest target account" , Option ['I'] ["ignore-assertions"] (NoArg (\o -> o { optIgnoreAssertions = True })) "ignore any failing balance assertions" , Option [] ["act"] (NoArg (\o -> o { optDCC = Just diffAct })) "use 'act' day counting convention" , Option [] ["30-360"] (NoArg (\o -> o { optDCC = Just diff30_360 })) "use '30/360' day counting convention" , Option [] ["30E-360"] (NoArg (\o -> o { optDCC = Just diff30E_360 })) "use '30E/360' day counting convention" , Option [] ["30E-360isda"] (NoArg (\o -> o { optDCC = Just diff30E_360isda })) "use '30E/360isda' day counting convention" , Option [] ["constant"] (ReqArg (\r o -> o { optRate = Just (constant (read r)) }) "RATE") "constant interest rate" , Option [] ["annual"] (ReqArg (\r o -> o { optRate = Just (perAnno (read r)) }) "RATE") "annual interest rate" , Option [] ["annual-schedule"] (ReqArg (\r o -> o { optRate = Just (perAnnoSchedule (read r)) }) "SCHEDULE") "schedule of annual interest rates.\nsyntax: '[(Date1,Rate1),(Date2,Rate2),...]'" , Option [] ["bgb288"] (NoArg (\o -> o { optRate = Just bgb288, optDCC = Just diffAct })) "compute interest according to German BGB288" , Option [] ["db24"] (NoArg (\o -> o { optRate = Just db24, optDCC = Just diff30E_360 })) "HACK: Deutsche Bank 24" , Option [] ["ing-diba"] (NoArg (\o -> o { optRate = Just ingDiba, optDCC = Just diffAct })) "HACK: compute interest according for Ing-Diba Tagesgeld account" ] usageMessage :: String usageMessage = usageInfo header options where header = "Usage: hledger-interest [OPTION...] ACCOUNT" commandLineError :: String -> IO a commandLineError err = do hPutStrLn stderr (err ++ usageMessage) exitFailure parseOpts :: [String] -> IO (Options, [String]) parseOpts argv = case getOpt Permute options argv of (o,n,[] ) -> return (foldl (flip id) defaultOptions o, n) (_,_,errs) -> commandLineError (concat errs) main :: IO () main = bracket (return ()) (\() -> hFlush stdout >> hFlush stderr) $ \() -> do (opts, args) <- getArgs >>= parseOpts when (optShowVersion opts) (putStrLn (showVersion version) >> exitSuccess) when (optShowHelp opts) (putStr usageMessage >> exitSuccess) when (null (optSourceAcc opts)) (commandLineError "required --source option is missing\n") when (null (optTargetAcc opts)) (commandLineError "required --target option is missing\n") when (isNothing (optDCC opts)) (commandLineError "no day counting convention specified\n") when (isNothing (optRate opts)) (commandLineError "no interest rate specified\n") let ledgerInputOptions = definputopts { ignore_assertions_ = optIgnoreAssertions opts } jnl' <- readJournalFiles ledgerInputOptions (reverse (optInput opts)) >>= either fail return interestAcc <- case args of [] -> commandLineError "required argument ACCOUNT is missing\n" [acc] -> return acc _ -> commandLineError "only one interest ACCOUNT may be specified\n" let jnl = filterJournalTransactions (Acct (toRegex' interestAcc)) jnl' ts = sortOn tdate (jtxns jnl) cfg = Config { interestAccount = T.pack interestAcc , sourceAccount = T.pack (optSourceAcc opts) , targetAccount = T.pack (optTargetAcc opts) , dayCountConvention = fromJust (optDCC opts) , interestRate = fromJust (optRate opts) } thisDay <- getCurrentDay let finalize | optBalanceToday opts = computeInterest thisDay | otherwise = return () ts' = runComputer cfg (mapM_ processTransaction ts >> finalize) result | optVerbose opts = ts' ++ ts | otherwise = ts' mapM_ (putStr . showTransactionUnelided) (sortOn tdate result) hledger-interest-1.6.0/README.md0000755000000000000000000001755107346545000014447 0ustar0000000000000000hledger-interest ================ hledger-interest is a small command-line utility based on [Simon Michael's hlegder library](http://hledger.org/). Its purpose is to compute interest for a given ledger account. Using command line flags, the program can be configured to use various [day counting conventions](http://en.wikipedia.org/wiki/Day_count_convention), such as "act/act", "30/360", "30E/360", and "30/360isda". Furthermore, it supports several of different interest schemes, i.e. annual interest with a fixed rate and the scheme mandated by the German law [§ 288 BGB Verzugszinsen](http://de.wikipedia.org/wiki/Verzugszinssatz). Extending support for other schemes is fairly easy, but currently requires hacking the source code. An overview over the available run-time options can be displayed by running "`hleder-interest --help`": Usage: hledger-interest [OPTION...] ACCOUNT -v --verbose echo input ledger to stdout (default) -q --quiet don't echo input ledger to stdout --today compute interest up until today -f FILE --file=FILE input ledger file (pass '-' for stdin) -s ACCOUNT --source=ACCOUNT interest source account -t ACCOUNT --target=ACCOUNT interest target account --act use 'act' day counting convention --30-360 use '30/360' day counting convention --30E-360 use '30E/360' day counting convention --30E-360isda use '30E/360isda' day counting convention --constant=RATE constant interest rate --annual=RATE annual interest rate --annual-schedule=SCHEDULE schedule of annual interest rates. syntax: '[(Date1,Rate1),(Date2,Rate2),...]' --bgb288 compute interest according to German BGB288 When run, hledger-interest reads the [ledger file](http://hledger.org/MANUAL.html#file-format) designated by the `--file` flag and filters all transactions that change the account specified on the command line. All other accounts will be ignored. Every time a transaction modifies the given account's balance -- thereby changing the amount of money that earns interest --, hledger-interest transfers the interest that accrued so far. Interest will be debited from the account designed by the `--source` flag and credited to the account designed by the `--target` flag. ## Examples Suppose that you've loaned 1000 Euro from your bank at an annual interest rate of 5%, and that you would like to see how interest develops over time. Then you would create a ledger file, say `loan.ledger`, that looks something like this: 2010/09/26 Loan Assets:Bank EUR 1000.00 Liabilities:Loan Now, `ledger-interest` is run to determine the interest up until today: $ hledger-interest -f loan.ledger --act --annual=0.05 --today -s Expenses:Interest -t Liabilities:Loan:Interest Liabilities:Loan 2010/09/26 Loan Assets:Bank EUR 1000.00 Liabilities:Loan 2010/12/31 5.00% interest for EUR -1000.00 over 96 days Liabilities:Loan:Interest EUR -13.15 Expenses:Interest 2011/08/22 5.00% interest for EUR -1000.00 over 234 days Liabilities:Loan:Interest EUR -32.05 Expenses:Interest Note a separate credit account for the interest was chosen: `Liabilities:Loan:Interest`. Consequently, interest accrued in one interest period does *not* earn interest in the following periods. If interest is credited to the main account instead, that behavior changes: $ hledger-interest -f loan.ledger --act --annual=0.05 --today -s Expenses:Interest -t Liabilities:Loan Liabilities:Loan 2010/09/26 Loan Assets:Bank EUR 1000.00 Liabilities:Loan 2010/12/31 5.00% interest for EUR -1000.00 over 96 days Liabilities:Loan EUR -13.15 Expenses:Interest 2011/08/22 5.00% interest for EUR -1013.15 over 234 days Liabilities:Loan EUR -32.48 Expenses:Interest Of course, loans are supposed to be paid back, and these payments change the amount of interest accrued. Suppose that `load.ledger` would be extended by the following transactions: 2010/12/11 Payment Assets:Bank EUR -150.00 Liabilities:Loan 2011/03/07 Payment Assets:Bank EUR -300.00 Liabilities:Loan 2011/08/21 Payment Assets:Bank EUR -150.00 Liabilities:Loan Then interest would develop as follows: $ hledger-interest -f loan.ledger --act --annual=0.05 -s Expenses:Interest -t Liabilities:Loan Liabilities:Loan 2010/09/26 Loan Assets:Bank EUR 1000.00 Liabilities:Loan 2010/12/11 5.00% interest for EUR -1000.00 over 76 days Liabilities:Loan EUR -10.41 Expenses:Interest 2010/12/11 Payment Assets:Bank EUR -150.00 Liabilities:Loan 2010/12/31 5.00% interest for EUR -860.41 over 20 days Liabilities:Loan EUR -2.36 Expenses:Interest 2011/03/07 5.00% interest for EUR -862.77 over 66 days Liabilities:Loan EUR -7.80 Expenses:Interest 2011/03/07 Payment Assets:Bank EUR -300.00 Liabilities:Loan 2011/08/21 5.00% interest for EUR -570.57 over 167 days Liabilities:Loan EUR -13.05 Expenses:Interest 2011/08/21 Payment Assets:Bank EUR -150.00 Liabilities:Loan Last but not least, there is a special case known as "Verzugszinsen" in German law, which applies when someone is supposed to pay a bill, but fails to do so on time. For every day past the deadline, interest accrues according to terms specified in [§ 247 BGB](http://www.gesetze-im-internet.de/bgb/__247.html). The command line flag `--bgb288` enables this scheme in `hledger-interest`. Let's assume that customer ACME is supposed to pay 35 Euro by 2010/09/15, but the money actually arrives almost half a year late: 2010/09/15 Services rendered to Customer ACME ACME 1 hour @ EUR 35.00 Receivable:ACME 2011/03/17 ACME ACME EUR 35.00 Receivable:ACME According to German law, you are entitled to the following interest: $ hledger-interest -f acme.ledger --quiet --bgb288 -s Income:Interest -t Receivable:ACME:Interest Receivable:ACME 2010/12/31 5.12% interest for EUR 35.00 over 107 days Receivable:ACME:Interest EUR 0.53 Income:Interest 2011/03/17 5.12% interest for EUR 35.00 over 76 days Receivable:ACME:Interest EUR 0.37 Income:Interest So, if you're smart, then you'll book the payment so that the accrued interest is paid *first*: 2011/03/17 ACME ACME EUR 35.00 Receivable:ACME:Interest EUR -0.90 Receivable:ACME This gives the following transaction history for the ACME account: $ hledger-interest -f acme.ledger --bgb288 -s Income:Interest -t Receivable:ACME:Interest Receivable:ACME | hledger -f - reg Receivable:ACME 2010/09/15 Services rendered .. Receivable:ACME EUR 35.00 EUR 35.00 2010/12/31 5.12% interest for.. Re:ACME:Interest EUR 0.53 EUR 35.53 2011/03/17 5.12% interest for.. Re:ACME:Interest EUR 0.37 EUR 35.90 2011/03/17 ACME Re:ACME:Interest EUR -0.90 EUR 35.00 Receivable:ACME EUR -34.10 EUR 0.90 hledger-interest-1.6.0/Setup.hs0000644000000000000000000000005607346545000014611 0ustar0000000000000000import Distribution.Simple main = defaultMain hledger-interest-1.6.0/hledger-interest.cabal0000644000000000000000000001222007346545000017402 0ustar0000000000000000Name: hledger-interest Version: 1.6.0 Synopsis: computes interest for a given account License: BSD3 License-file: LICENSE Author: Peter Simons Maintainer: Peter Simons Homepage: https://github.com/peti/hledger-interest Category: Finance Build-type: Simple Cabal-version: >= 1.10 Extra-source-files: README.md Stability: stable tested-with: GHC == 8.0.2, GHC == 8.2.2, GHC == 8.4.4, GHC == 8.6.5 , GHC == 8.8.4, GHC == 8.10.2 Description: hledger-interest is a small command-line utility based on Simon Michael's hleder library. Its purpose is to compute interest for a given ledger account. Using command line flags, the program can be configured to use various schemes for day-counting, such as act\/act, 30\/360, 30E\/360, and 30\/360isda. Furthermore, it supports a (small) number of interest schemes, i.e. annual interest with a fixed rate and the scheme mandated by the German BGB288 (Basiszins fuer Verbrauchergeschaefte). Extending support for other schemes is fairly easy, but currently requires changes to the source code. . As an example, consider the following loan, stored in a file called @test.ledger@: . > 2008/09/26 Loan > Assets:Bank EUR 10000.00 > Liabilities:Bank > > 2008/11/27 Payment > Assets:Bank EUR -3771.12 > Liabilities:Bank > > 2009/05/03 Payment > Assets:Bank EUR -1200.00 > Liabilities:Bank > > 2010/12/10 Payment > Assets:Bank EUR -3700.00 > Liabilities:Bank . Suppose that loan earns 5% interest per year, and payments amortize interest before amortizing the principal claim, then the resulting ledger would look like this: . > $ hledger-interest --file=test.ledger --source=Expenses:Interest --target=Liabilities:Bank --30-360 --annual=0.05 Liabilities:Bank > 2008/09/26 Loan > Assets:Bank EUR 10000.00 > Liabilities:Bank > > 2008/11/27 Payment > Assets:Bank EUR -3771.12 > Liabilities:Bank > > 2008/11/27 5.00% interest for EUR -10000.00 over 61 days > Liabilities:Bank EUR -84.72 > Expenses:Interest > > 2008/12/31 5.00% interest for EUR -6313.60 over 34 days > Liabilities:Bank EUR -29.81 > Expenses:Interest > > 2009/05/03 Payment > Assets:Bank EUR -1200.00 > Liabilities:Bank > > 2009/05/03 5.00% interest for EUR -6343.42 over 123 days > Liabilities:Bank EUR -108.37 > Expenses:Interest > > 2009/12/31 5.00% interest for EUR -5251.78 over 238 days > Liabilities:Bank EUR -173.60 > Expenses:Interest > > 2010/12/10 Payment > Assets:Bank EUR -3700.00 > Liabilities:Bank > > 2010/12/10 5.00% interest for EUR -5425.38 over 340 days > Liabilities:Bank EUR -256.20 > Expenses:Interest > > 2010/12/31 5.00% interest for EUR -1981.58 over 21 days > Liabilities:Bank EUR -5.78 > Expenses:Interest . Running the utility with @--help@ gives a brief overview over the available options: . > Usage: hledger-interest [OPTION...] ACCOUNT > -h --help print this message and exit > -V --version show version number and exit > -v --verbose echo input ledger to stdout (default) > -q --quiet don't echo input ledger to stdout > --today compute interest up until today > -f FILE --file=FILE input ledger file (pass '-' for stdin) > -s ACCOUNT --source=ACCOUNT interest source account > -t ACCOUNT --target=ACCOUNT interest target account > -I --ignore-assertions ignore any failing balance assertions > --act use 'act' day counting convention > --30-360 use '30/360' day counting convention > --30E-360 use '30E/360' day counting convention > --30E-360isda use '30E/360isda' day counting convention > --constant=RATE constant interest rate > --annual-schedule=SCHEDULE schedule of annual interest rates. > syntax: '[(Date1,Rate1),(Date2,Rate2),...]' > --annual=RATE annual interest rate > --bgb288 compute interest according to German BGB288 Source-Repository head Type: git Location: git://github.com/peti/hledger-interest.git Executable hledger-interest default-language: Haskell2010 Main-is: Main.hs Build-depends: base >= 3 && < 5, hledger-lib == 1.19.*, time, mtl, Cabal, Decimal, text other-modules: Hledger.Interest Hledger.Interest.DayCountConvention Hledger.Interest.Rate Paths_hledger_interest