preliminary haddockification

This commit is contained in:
Simon Michael 2008-10-01 00:29:58 +00:00
parent 3ca87d0486
commit efcbd29dc8
11 changed files with 100 additions and 90 deletions

View File

@ -18,12 +18,12 @@ accountNameLevel :: AccountName -> Int
accountNameLevel "" = 0
accountNameLevel a = (length $ filter (==sepchar) a) + 1
-- ["a:b:c","d:e"] -> ["a","a:b","a:b:c","d","d:e"]
-- | ["a:b:c","d:e"] -> ["a","a:b","a:b:c","d","d:e"]
expandAccountNames :: [AccountName] -> [AccountName]
expandAccountNames as = nub $ concat $ map expand as
where expand as = map accountNameFromComponents (tail $ inits $ accountNameComponents as)
-- ["a:b:c","d:e"] -> ["a","d"]
-- | ["a:b:c","d:e"] -> ["a","d"]
topAccountNames :: [AccountName] -> [AccountName]
topAccountNames as = [a | a <- expandAccountNames as, accountNameLevel a == 1]
@ -46,7 +46,7 @@ s `isSubAccountNameOf` p =
subAccountNamesFrom :: [AccountName] -> AccountName -> [AccountName]
subAccountNamesFrom accts a = filter (`isSubAccountNameOf` a) accts
-- We could almost get by with just the above, but we need smarter
-- | We could almost get by with just the above, but we need smarter
-- structures to eg display the account tree with boring accounts elided.
-- first, here is a tree of AccountNames; Account and Account tree are
-- defined later.

View File

@ -1,10 +1,4 @@
module Amount
where
import Utils
import Types
import Currency
{-
{-|
a simple amount is a currency, quantity pair:
$1
@ -37,6 +31,12 @@ arithmetic:
-}
module Amount
where
import Utils
import Types
import Currency
tests = runTestTT $ test [
show (dollars 1) ~?= "$1.00"
,show (hours 1) ~?= "1h" -- currently h1.00
@ -80,13 +80,13 @@ instance Num Amount where
(-) = amountop (-)
(*) = amountop (*)
-- problem: when an integer is converted to an amount it must pick a
-- | problem: when an integer is converted to an amount it must pick a
-- precision, which we specify here (should be infinite ?). This can
-- affect amount arithmetic, in particular the sum of a list of amounts.
-- So, we may need to adjust the precision after summing amounts.
amtintprecision = 2
-- apply op to two amounts, adopting a's currency and lowest precision
-- | apply op to two amounts, adopting a's currency and lowest precision
amountop :: (Double -> Double -> Double) -> Amount -> Amount -> Amount
amountop op (Amount ac aq ap) b@(Amount _ _ bp) =
Amount ac (aq `op` (quantity $ toCurrency ac b)) (min ap bp)

View File

@ -22,7 +22,7 @@ getcurrency s = Map.findWithDefault (Currency s 1) s currencymap
conversionRate :: Currency -> Currency -> Double
conversionRate oldc newc = (rate newc) / (rate oldc)
-- convenient amount constructors
-- | convenient amount constructors
dollars n = Amount (getcurrency "$") n 2
euro n = Amount (getcurrency "EUR") n 2
pounds n = Amount (getcurrency "£") n 2

View File

@ -34,7 +34,7 @@ instance Show Ledger where
(length $ periodic_entries $ rawledger l))
(length $ accountnames l)
-- at startup, to improve performance, we refine the parsed ledger entries:
-- | at startup, to improve performance, we refine the parsed ledger entries:
-- 1. filter based on account/description patterns, if any
-- 2. cache per-account info
-- also, figure out the precision(s) to use
@ -62,7 +62,7 @@ cacheLedger pats l =
in
Ledger l' ant amap lprecision
-- filter entries by description and whether any transactions match account patterns
-- | filter entries by description and whether any transactions match account patterns
filterLedgerEntries :: FilterPatterns -> LedgerFile -> LedgerFile
filterLedgerEntries (acctpat,descpat) (LedgerFile ms ps es f) =
LedgerFile ms ps (filter matchdesc $ filter (any matchtxn . etransactions) es) f
@ -74,7 +74,7 @@ filterLedgerEntries (acctpat,descpat) (LedgerFile ms ps es f) =
Nothing -> False
otherwise -> True
-- filter transactions in each ledger entry by account patterns
-- | filter transactions in each ledger entry by account patterns
-- this may unbalance entries
filterLedgerTransactions :: FilterPatterns -> LedgerFile -> LedgerFile
filterLedgerTransactions (acctpat,descpat) (LedgerFile ms ps es f) =
@ -93,7 +93,7 @@ accountnames l = flatten $ accountnametree l
ledgerAccount :: Ledger -> AccountName -> Account
ledgerAccount l a = (accounts l) ! a
-- This sets all amount precisions to that of the highest-precision
-- | This sets all amount precisions to that of the highest-precision
-- amount, to help with report output. It should perhaps be done in the
-- display functions, but those are far removed from the ledger. Keep in
-- mind if doing more arithmetic with these.
@ -110,7 +110,7 @@ ledgerAccountTree l depth =
addDataToAccountNameTree :: Ledger -> Tree AccountName -> Tree Account
addDataToAccountNameTree = treemap . ledgerAccount
-- balance report support
-- | balance report support
--
-- examples: here is a sample account tree:
--
@ -130,6 +130,7 @@ addDataToAccountNameTree = treemap . ledgerAccount
-- standard balance command shows all top-level accounts:
--
-- > ledger bal
--
-- $ assets
-- $ equity
-- $ expenses
@ -139,19 +140,24 @@ addDataToAccountNameTree = treemap . ledgerAccount
-- with an account pattern, show only the ones with matching names:
--
-- > ledger bal asset
--
-- $ assets
--
-- with -s, show all subaccounts of matched accounts:
--
-- > ledger -s bal asset
--
-- $ assets
-- $ cash
-- $ checking
-- $ saving
--
-- we elide boring accounts in two ways:
--
-- - leaf accounts and branches with 0 balance or 0 transactions are omitted
--
-- - inner accounts with 0 transactions and 1 subaccount are displayed inline
--
-- so this:
--
-- a (0 txns)

View File

@ -8,7 +8,7 @@ import Amount
instance Show LedgerEntry where show = showEntryDescription
-- for register report
-- | for register report
--
-- a register entry is displayed as two or more lines like this:
-- date description account amount balance
@ -25,7 +25,7 @@ showEntryDescription e = (showDate $ edate e) ++ " " ++ (showDescription $ edesc
showDate d = printf "%-10s" d
showDescription s = printf "%-20s" (elideRight 20 s)
-- quick & dirty: checks entry's 0 balance only to 8 places
-- | quick & dirty: checks entry's 0 balance only to 8 places
isEntryBalanced :: LedgerEntry -> Bool
isEntryBalanced = ((0::Double)==) . read . printf "%0.8f" . quantity . sumLedgerTransactions . etransactions
@ -36,7 +36,7 @@ autofillEntry e@(LedgerEntry _ _ _ _ _ ts _) =
True -> e'
False -> (error $ "transactions don't balance in " ++ show e)
-- the print command shows cleaned up ledger file entries, something like:
-- | the print command shows cleaned up ledger file entries, something like:
--
-- yyyy/mm/dd[ *][ CODE] description......... [ ; comment...............]
-- account name 1..................... ...$amount1[ ; comment...............]

View File

@ -1,4 +1,4 @@
-- all data types & behaviours
{-| all data types & behaviours -}
module Models (
module Types,
module Currency,

View File

@ -51,7 +51,7 @@ usage = usageInfo usagehdr options
ledgerFilePath :: [Flag] -> IO String
ledgerFilePath = findFileFromOpts "~/ledger.dat" "LEDGER"
-- find a file path from options, an env var or a default value
-- | find a file path from options, an env var or a default value
findFileFromOpts :: FilePath -> String -> [Flag] -> IO String
findFileFromOpts defaultpath envvar opts = do
envordefault <- getEnv envvar `catch` \_ -> return defaultpath
@ -72,7 +72,7 @@ tildeExpand ('~':'/':xs) = getHomeDirectory >>= return . (++ ('/':xs))
tildeExpand xs = return xs
-- -- courtesy of allberry_b
-- ledger pattern args are 0 or more account patterns optionally followed
-- | ledger pattern args are 0 or more account patterns optionally followed
-- by -- and 0 or more description patterns
parsePatternArgs :: [String] -> FilterPatterns
parsePatternArgs args = argpats as ds'

View File

@ -1,45 +1,9 @@
module Parse
where
import qualified Data.Map as Map
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Language
import qualified Text.ParserCombinators.Parsec.Token as P
import System.IO
{-|
standard ledger file parser
import Utils
import Models
Here's the ledger grammar from the ledger 2.5 manual:
-- set up token parsing, though we're not yet using these much
ledgerLanguageDef = LanguageDef {
commentStart = ""
, commentEnd = ""
, commentLine = ";"
, nestedComments = False
, identStart = letter <|> char '_'
, identLetter = alphaNum <|> oneOf "_':"
, opStart = opLetter emptyDef
, opLetter = oneOf "!#$%&*+./<=>?@\\^|-~"
, reservedOpNames= []
, reservedNames = []
, caseSensitive = False
}
lexer = P.makeTokenParser ledgerLanguageDef
whiteSpace = P.whiteSpace lexer
lexeme = P.lexeme lexer
symbol = P.symbol lexer
natural = P.natural lexer
parens = P.parens lexer
semi = P.semi lexer
identifier = P.identifier lexer
reserved = P.reserved lexer
reservedOp = P.reservedOp lexer
-- standard ledger file parser
{-
Here's the ledger 2.5 grammar:
"The ledger file format is quite simple, but also very flexible. It supports
The ledger file format is quite simple, but also very flexible. It supports
many options, though typically the user can ignore most of them. They are
summarized below. The initial character of each line determines what the
line means, and how it should be interpreted. Allowable initial characters
@ -64,7 +28,7 @@ NUMBER A line beginning with a number denotes an entry. It may be followed
The ACCOUNT may be surrounded by parentheses if it is a virtual
transactions, or square brackets if it is a virtual transactions that must
balance. The AMOUNT can be followed by a per-unit transaction cost,
by specifying AMOUNT, or a complete transaction cost with @ AMOUNT.
by specifying AMOUNT, or a complete transaction cost with \@ AMOUNT.
Lastly, the NOTE may specify an actual and/or effective date for the
transaction by using the syntax [ACTUAL_DATE] or [=EFFECTIVE_DATE] or
[ACTUAL_DATE=EFFECtIVE_DATE].
@ -79,7 +43,6 @@ NUMBER A line beginning with a number denotes an entry. It may be followed
After this initial line there should be a set of one or more transactions, just as
if it were normal entry.
! A line beginning with an exclamation mark denotes a command directive. It
must be immediately followed by the command word. The supported commands
are:
@ -132,10 +95,51 @@ C AMOUNT1 = AMOUNT2
i, o, b, h
These four relate to timeclock support, which permits ledger to read timelog
files. See the timeclocks documentation for more info on the syntax of its
timelog files."
timelog files.
parsec example: http://pandoc.googlecode.com/svn/trunk/src/Text/Pandoc/Readers/RST.hs
sample data in Tests.hs
-}
-- parsec example: http://pandoc.googlecode.com/svn/trunk/src/Text/Pandoc/Readers/RST.hs
-- sample data in Tests.hs
module Parse
where
import qualified Data.Map as Map
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Language
import qualified Text.ParserCombinators.Parsec.Token as P
import System.IO
import Utils
import Models
-- set up token parsing, though we're not yet using these much
ledgerLanguageDef = LanguageDef {
commentStart = ""
, commentEnd = ""
, commentLine = ";"
, nestedComments = False
, identStart = letter <|> char '_'
, identLetter = alphaNum <|> oneOf "_':"
, opStart = opLetter emptyDef
, opLetter = oneOf "!#$%&*+./<=>?@\\^|-~"
, reservedOpNames= []
, reservedNames = []
, caseSensitive = False
}
lexer = P.makeTokenParser ledgerLanguageDef
whiteSpace = P.whiteSpace lexer
lexeme = P.lexeme lexer
symbol = P.symbol lexer
natural = P.natural lexer
parens = P.parens lexer
semi = P.semi lexer
identifier = P.identifier lexer
reserved = P.reserved lexer
reservedOp = P.reservedOp lexer
ledgerfile :: Parser LedgerFile
ledgerfile = ledger <|> ledgerfromtimelog
@ -239,7 +243,7 @@ ledgertransaction = do
restofline
return (LedgerTransaction account amount comment)
-- account names may have single spaces in them, and are terminated by two or more spaces
-- | account names may have single spaces in them, and are terminated by two or more spaces
ledgeraccount :: Parser String
ledgeraccount =
many1 ((alphaNum <|> char ':' <|> char '/' <|> char '_' <?> "account name")
@ -271,7 +275,7 @@ whiteSpace1 :: Parser ()
whiteSpace1 = do space; whiteSpace
-- timelog file parser
-- | timelog file parser
{-
timelog grammar, from timeclock.el 2.6

View File

@ -13,7 +13,7 @@ instance Show Transaction where
show (Transaction eno d desc a amt) =
unwords [d,desc,a,show amt]
-- we use the entry number e to remember the grouping of txns
-- | we use the entry number e to remember the grouping of txns
flattenEntry :: (LedgerEntry, Int) -> [Transaction]
flattenEntry (LedgerEntry d _ _ desc _ ts _, e) =
[Transaction e d desc (taccount t) (tamount t) | t <- ts]
@ -27,7 +27,7 @@ accountNamesFromTransactions ts = nub $ map account ts
sumTransactions :: [Transaction] -> Amount
sumTransactions = sum . map amount
-- for register command
-- | for register command
showTransactionsWithBalances :: [Transaction] -> Amount -> String
showTransactionsWithBalances [] _ = []

View File

@ -30,7 +30,7 @@ hledger
-}
-- account and description-matching patterns
-- | account and description-matching patterns
type FilterPatterns = (Maybe Regex, Maybe Regex)
type Date = String
@ -42,25 +42,25 @@ data Currency = Currency {
rate :: Double -- relative to the dollar.. 0 rates not supported yet
} deriving (Eq,Show)
-- some amount of money, time, stock, oranges, etc.
-- | some amount of money, time, stock, oranges, etc.
data Amount = Amount {
currency :: Currency,
quantity :: Double,
precision :: Int -- number of significant decimal places
precision :: Int -- ^ number of significant decimal places
} deriving (Eq)
-- AccountNames are strings like "assets:cash:petty", from which we derive
-- the chart of accounts
type AccountName = String
-- a line item in a ledger entry
-- | a line item in a ledger entry
data LedgerTransaction = LedgerTransaction {
taccount :: AccountName,
tamount :: Amount,
tcomment :: String
} deriving (Eq)
-- a ledger entry, with two or more balanced transactions
-- | a ledger entry, with two or more balanced transactions
data LedgerEntry = LedgerEntry {
edate :: Date,
estatus :: Bool,
@ -71,19 +71,19 @@ data LedgerEntry = LedgerEntry {
epreceding_comment_lines :: String
} deriving (Eq)
-- an automated ledger entry
-- | an automated ledger entry
data ModifierEntry = ModifierEntry {
valueexpr :: String,
m_transactions :: [LedgerTransaction]
} deriving (Eq)
-- a periodic ledger entry
-- | a periodic ledger entry
data PeriodicEntry = PeriodicEntry {
periodexpr :: String,
p_transactions :: [LedgerTransaction]
} deriving (Eq)
-- we also parse timeclock.el timelogs
-- | we also parse timeclock.el timelogs
data TimeLogEntry = TimeLogEntry {
tlcode :: Char,
tldatetime :: DateTime,
@ -94,7 +94,7 @@ data TimeLog = TimeLog {
timelog_entries :: [TimeLogEntry]
} deriving (Eq)
-- a parsed ledger file
-- | a parsed ledger file
data LedgerFile = LedgerFile {
modifier_entries :: [ModifierEntry],
periodic_entries :: [PeriodicEntry],
@ -102,7 +102,7 @@ data LedgerFile = LedgerFile {
final_comment_lines :: String
} deriving (Eq)
-- we flatten LedgerEntries and LedgerTransactions into Transactions,
-- | we flatten LedgerEntries and LedgerTransactions into Transactions,
-- which are simpler to query at the cost of some data duplication
data Transaction = Transaction {
entryno :: Int,
@ -112,14 +112,14 @@ data Transaction = Transaction {
amount :: Amount
} deriving (Eq)
-- cached information for a particular account
-- | cached information for a particular account
data Account = Account {
aname :: AccountName,
atransactions :: [Transaction], -- excludes sub-accounts
abalance :: Amount -- includes sub-accounts
atransactions :: [Transaction], -- ^ excludes sub-accounts
abalance :: Amount -- ^ includes sub-accounts
}
-- a ledger with account information cached for faster queries
-- | a ledger with account information cached for faster queries
data Ledger = Ledger {
rawledger :: LedgerFile,
accountnametree :: Tree AccountName,

View File

@ -71,7 +71,7 @@ balance opts pats = do
-- helpers for interacting in ghci
-- returns a Ledger parsed from the file your LEDGER environment variable
-- | returns a Ledger parsed from the file your LEDGER environment variable
-- points to or (WARNING:) an empty one if there was a problem.
myledger :: IO Ledger
myledger = do
@ -79,7 +79,7 @@ myledger = do
let ledgerfile = either (\_ -> LedgerFile [] [] [] "") id parsed
return $ cacheLedger (argpats [] []) ledgerfile
-- similar, but accepts a file path
-- | similar, but accepts a file path
ledgerfromfile :: String -> IO Ledger
ledgerfromfile f = do
parsed <- ledgerFilePath [File f] >>= parseLedgerFile
@ -88,7 +88,7 @@ ledgerfromfile f = do
accountnamed :: AccountName -> IO Account
accountnamed a = myledger >>= (return . fromMaybe nullacct . Map.lookup a . accounts)
--clearedBalanceToDate :: String -> Amount