move type docs to the corresponding module descriptions and update

This commit is contained in:
Simon Michael 2008-10-03 02:04:15 +00:00
parent 7f5d85cea4
commit 6ce6029c7a
14 changed files with 92 additions and 31 deletions

View File

@ -1,5 +1,10 @@
{-| {-|
The Ledger package allows parsing and querying of ledger files.
It generally provides a compatible subset of C++ ledger's functionality.
-} -}
module Ledger ( module Ledger (
module Ledger.Types, module Ledger.Types,
module Ledger.Currency, module Ledger.Currency,

View File

@ -1,3 +1,11 @@
{-|
An 'Account' stores an account name, all transactions in the account
(excluding any subaccounts), and the total balance (including any
subaccounts).
-}
module Ledger.Account module Ledger.Account
where where
import Ledger.Utils import Ledger.Utils

View File

@ -1,3 +1,10 @@
{-|
'AccountName's are strings like @assets:cash:petty@.
From a set of these we derive the account hierarchy.
-}
module Ledger.AccountName module Ledger.AccountName
where where
import Ledger.Utils import Ledger.Utils
@ -49,8 +56,8 @@ subAccountNamesFrom accts a = filter (`isSubAccountNameOf` a) accts
-- | We could almost get by with just the AccountName manipulations -- | We could almost get by with just the AccountName manipulations
-- above, but we need smarter structures to eg display the account -- above, but we need smarter structures to eg display the account
-- tree with boring accounts elided. This converts a list of -- tree with boring accounts elided. This converts a list of
-- AccountNames to a tree (later we will convert that to a tree of -- AccountName to a tree (later we will convert that to a tree of
-- Accounts.) -- 'Account'.)
accountNameTreeFrom_props = accountNameTreeFrom_props =
[ [
accountNameTreeFrom ["a"] == Node "top" [Node "a" []], accountNameTreeFrom ["a"] == Node "top" [Node "a" []],

View File

@ -1,5 +1,7 @@
{-| {-|
A simple amount is a currency, quantity pair: An 'Amount' is some quantity of money, shares, or anything else.
A simple amount is a currency, quantity pair (where currency can be anything):
@ @
$1 $1
@ -7,11 +9,11 @@ A simple amount is a currency, quantity pair:
EUR 3.44 EUR 3.44
GOOG 500 GOOG 500
1.5h 1.5h
90m 90apples
0 0
@ @
A mixed amount is one or more simple amounts: A mixed amount (not yet implemented) is one or more simple amounts:
@ @
$50, EUR 3, AAPL 500 $50, EUR 3, AAPL 500

View File

@ -1,3 +1,10 @@
{-|
A 'Currency' is a symbol and a conversion rate relative to the
dollar. Currency symbols are parsed from the ledger file, rates are
currently hard-coded.
-}
module Ledger.Currency module Ledger.Currency
where where
import qualified Data.Map as Map import qualified Data.Map as Map

View File

@ -1,3 +1,10 @@
{-|
A 'Ledger' stores, for efficiency, a 'RawLedger' plus its tree of account
names, a map from account names to 'Account's, and the display precision.
-}
module Ledger.Ledger module Ledger.Ledger
where where
import qualified Data.Map as Map import qualified Data.Map as Map

View File

@ -1,3 +1,10 @@
{-|
A 'LedgerEntry' represents a normal entry in the ledger file. It contains
two or more 'RawTransaction's which balance.
-}
module Ledger.LedgerEntry module Ledger.LedgerEntry
where where
import Ledger.Utils import Ledger.Utils

View File

@ -1,3 +1,10 @@
{-|
A 'RawLedger' is a parsed ledger file. We call it raw to distinguish from
the cached 'Ledger'.
-}
module Ledger.RawLedger module Ledger.RawLedger
where where
import qualified Data.Map as Map import qualified Data.Map as Map

View File

@ -1,3 +1,10 @@
{-|
A 'RawTransaction' represents a single transaction line within a ledger
entry. We call it raw to distinguish from the cached 'Transaction'.
-}
module Ledger.RawTransaction module Ledger.RawTransaction
where where
import Ledger.Utils import Ledger.Utils

View File

@ -1,3 +1,10 @@
{-|
A 'TimeLog' is a parsed timelog file (generated by timeclock.el).
It contains zero or more 'TimeLogEntry's.
-}
module Ledger.TimeLog module Ledger.TimeLog
where where
import Ledger.Utils import Ledger.Utils

View File

@ -1,3 +1,10 @@
{-|
A 'Transaction' is a 'RawTransaction' with its parent 'LedgerEntry' \'s
date and description attached, for easier querying.
-}
module Ledger.Transaction module Ledger.Transaction
where where
import Ledger.Utils import Ledger.Utils
@ -13,7 +20,9 @@ instance Show Transaction where
show (Transaction eno d desc a amt) = show (Transaction eno d desc a amt) =
unwords [d,desc,a,show amt] unwords [d,desc,a,show amt]
-- | we use the entry number e to remember the grouping of txns -- | Convert a 'LedgerEntry' to two or more 'Transaction's. An id number
-- is attached to the transactions to preserve their grouping - it should
-- be unique per entry.
flattenEntry :: (LedgerEntry, Int) -> [Transaction] flattenEntry :: (LedgerEntry, Int) -> [Transaction]
flattenEntry (LedgerEntry d _ _ desc _ ts _, e) = flattenEntry (LedgerEntry d _ _ desc _ ts _, e) =
[Transaction e d desc (taccount t) (tamount t) | t <- ts] [Transaction e d desc (taccount t) (tamount t) | t <- ts]

View File

@ -1,36 +1,32 @@
{-| {-|
All the main data types, defined here to avoid import cycles. All the main data types, defined here to avoid import cycles.
See the corresponding modules for documentation.
-} -}
module Ledger.Types module Ledger.Types
where where
import Ledger.Utils import Ledger.Utils
import qualified Data.Map as Map import qualified Data.Map as Map
-- | a date
type Date = String type Date = String
-- | a date and time
type DateTime = String type DateTime = String
-- | the currency of an Amount.
data Currency = Currency { data Currency = Currency {
symbol :: String, symbol :: String,
rate :: Double -- ^ relative to the dollar (rates are currently hardcoded) rate :: Double
} deriving (Eq,Show) } deriving (Eq,Show)
-- | some amount of money, shares, or anything else.
data Amount = Amount { data Amount = Amount {
currency :: Currency, currency :: Currency,
quantity :: Double, quantity :: Double,
precision :: Int -- ^ number of significant decimal places precision :: Int -- ^ number of significant decimal places
} deriving (Eq) } deriving (Eq)
-- | AccountNames are strings like @assets:cash:petty@, from which we derive
-- the chart of accounts
type AccountName = String type AccountName = String
-- | a single transaction line within a ledger entry. We call it raw to
-- distinguish from the cached 'Transaction'.
data RawTransaction = RawTransaction { data RawTransaction = RawTransaction {
taccount :: AccountName, taccount :: AccountName,
tamount :: Amount, tamount :: Amount,
@ -49,7 +45,6 @@ data PeriodicEntry = PeriodicEntry {
p_transactions :: [RawTransaction] p_transactions :: [RawTransaction]
} deriving (Eq) } deriving (Eq)
-- | a regular ledger entry, containing two or more transactions which balance
data LedgerEntry = LedgerEntry { data LedgerEntry = LedgerEntry {
edate :: Date, edate :: Date,
estatus :: Bool, estatus :: Bool,
@ -60,8 +55,6 @@ data LedgerEntry = LedgerEntry {
epreceding_comment_lines :: String epreceding_comment_lines :: String
} deriving (Eq) } deriving (Eq)
-- | a parsed ledger file. We call it raw to distinguish from the cached
-- 'Ledger'.
data RawLedger = RawLedger { data RawLedger = RawLedger {
modifier_entries :: [ModifierEntry], modifier_entries :: [ModifierEntry],
periodic_entries :: [PeriodicEntry], periodic_entries :: [PeriodicEntry],
@ -69,22 +62,16 @@ data RawLedger = RawLedger {
final_comment_lines :: String final_comment_lines :: String
} deriving (Eq) } deriving (Eq)
-- | a timelog entry in a timelog file (generated by timeclock.el)
data TimeLogEntry = TimeLogEntry { data TimeLogEntry = TimeLogEntry {
tlcode :: Char, tlcode :: Char,
tldatetime :: DateTime, tldatetime :: DateTime,
tlcomment :: String tlcomment :: String
} deriving (Eq,Ord) } deriving (Eq,Ord)
-- | a parsed timelog file
data TimeLog = TimeLog { data TimeLog = TimeLog {
timelog_entries :: [TimeLogEntry] timelog_entries :: [TimeLogEntry]
} deriving (Eq) } deriving (Eq)
-- | optimisations: these types provide some caching and are easier to work with.
--
-- A Transaction is a RawTransaction with some of its parent
-- LedgerEntry's data attached.
data Transaction = Transaction { data Transaction = Transaction {
entryno :: Int, entryno :: Int,
date :: Date, date :: Date,
@ -93,16 +80,12 @@ data Transaction = Transaction {
amount :: Amount amount :: Amount
} deriving (Eq) } deriving (Eq)
-- | an Account stores an account name, all transactions in the account
-- (excluding subaccounts), and the total balance (including subaccounts).
data Account = Account { data Account = Account {
aname :: AccountName, aname :: AccountName,
atransactions :: [Transaction], atransactions :: [Transaction],
abalance :: Amount abalance :: Amount
} }
-- | a raw ledger plus its tree of account names, a map from account names
-- to Accounts, and the preferred precision.
data Ledger = Ledger { data Ledger = Ledger {
rawledger :: RawLedger, rawledger :: RawLedger,
accountnametree :: Tree AccountName, accountnametree :: Tree AccountName,

View File

@ -1,4 +1,9 @@
-- standard always-available imports and utilities {-|
Standard always-available imports and utilities.
-}
module Ledger.Utils ( module Ledger.Utils (
module Ledger.Utils, module Ledger.Utils,
module Char, module Char,

View File

@ -93,7 +93,7 @@ wildcard :: Regex
wildcard = mkRegex ".*" wildcard = mkRegex ".*"
-- | parse the user's specified ledger file and do some action with it -- | parse the user's specified ledger file and do some action with it
-- (or report a parse error) -- (or report a parse error). This function makes the whole thing go.
parseLedgerAndDo :: [Flag] -> (Regex,Regex) -> (Ledger -> IO ()) -> IO () parseLedgerAndDo :: [Flag] -> (Regex,Regex) -> (Ledger -> IO ()) -> IO ()
parseLedgerAndDo opts pats cmd = do parseLedgerAndDo opts pats cmd = do
path <- ledgerFilePath opts path <- ledgerFilePath opts