move types to bottom

This commit is contained in:
Simon Michael 2007-07-02 16:43:14 +00:00
parent 224c05aa22
commit 2ddeb4841c
14 changed files with 158 additions and 119 deletions

View File

@ -14,11 +14,6 @@ import Ledger
-- an Account caches an account's name, balance (including sub-accounts) -- an Account caches an account's name, balance (including sub-accounts)
-- and transactions (excluding sub-accounts) -- and transactions (excluding sub-accounts)
data Account = Account {
aname :: AccountName,
atransactions :: [EntryTransaction],
abalance :: Amount
}
instance Show Account where instance Show Account where
show (Account a ts b) = printf "Account %s with %d transactions" a $ length ts show (Account a ts b) = printf "Account %s with %d transactions" a $ length ts

View File

@ -5,7 +5,6 @@ import Types
-- AccountNames are strings like "assets:cash:petty"; from these we build -- AccountNames are strings like "assets:cash:petty"; from these we build
-- the chart of accounts, which should be a simple hierarchy. -- the chart of accounts, which should be a simple hierarchy.
type AccountName = String
accountNameComponents :: AccountName -> [String] accountNameComponents :: AccountName -> [String]
accountNameComponents = splitAtElement ':' accountNameComponents = splitAtElement ':'

View File

@ -2,8 +2,9 @@ module Amount
where where
import Utils import Utils
import Types import Types
import Currency
{- {-
a simple amount is a currency, quantity pair: a simple amount is a currency, quantity pair:
$1 $1
@ -40,43 +41,6 @@ tests = runTestTT $ test [
parseAmount "$1" ~?= dollars 1 -- currently 0 parseAmount "$1" ~?= dollars 1 -- currently 0
] ]
-- currency
data Currency = Currency {
symbol :: String,
rate :: Double -- relative to the dollar
} deriving (Eq,Show)
currencies =
[
Currency "$" 1
,Currency "EUR" 0.760383
,Currency "£" 0.512527
,Currency "h" 60 -- hours
,Currency "m" 1 -- minutes
]
getcurrency :: String -> Currency
getcurrency s = head $ [(Currency symbol rate) | (Currency symbol rate) <- currencies, symbol==s]
-- convenience
dollars = Amount $ getcurrency "$"
euro = Amount $ getcurrency "EUR"
pounds = Amount $ getcurrency "£"
hours = Amount $ getcurrency "h"
minutes = Amount $ getcurrency "m"
conversionRate :: Currency -> Currency -> Double
conversionRate oldc newc = (rate newc) / (rate oldc)
-- amount
data Amount = Amount {
currency :: Currency,
quantity :: Double
} deriving (Eq)
instance Show Amount where show = showAmountRoundedOrZero instance Show Amount where show = showAmountRoundedOrZero
nullamt = dollars 0 nullamt = dollars 0
@ -107,8 +71,3 @@ toCurrency :: Currency -> Amount -> Amount
toCurrency newc (Amount oldc q) = toCurrency newc (Amount oldc q) =
Amount newc (q * (conversionRate oldc newc)) Amount newc (q * (conversionRate oldc newc))
-- mixed amounts
--data MixedAmount = MixedAmount [Amount] deriving (Eq,Ord)

27
Currency.hs Normal file
View File

@ -0,0 +1,27 @@
module Currency
where
import Utils
import Types
currencies =
[
Currency "$" 1
,Currency "EUR" 0.760383
,Currency "£" 0.512527
,Currency "h" 60 -- hours
,Currency "m" 1 -- minutes
]
getcurrency :: String -> Currency
getcurrency s = head $ [(Currency symbol rate) | (Currency symbol rate) <- currencies, symbol==s]
conversionRate :: Currency -> Currency -> Double
conversionRate oldc newc = (rate newc) / (rate oldc)
-- convenient amount constructors
dollars = Amount $ getcurrency "$"
euro = Amount $ getcurrency "EUR"
pounds = Amount $ getcurrency "£"
hours = Amount $ getcurrency "h"
minutes = Amount $ getcurrency "m"

View File

@ -6,8 +6,6 @@ import Types
import Transaction import Transaction
type EntryStatus = Bool
-- a register entry is displayed as two or more lines like this: -- a register entry is displayed as two or more lines like this:
-- date description account amount balance -- date description account amount balance
-- DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaaaaa AAAAAAAAAAA AAAAAAAAAAAA -- DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaaaaa AAAAAAAAAAA AAAAAAAAAAAA
@ -19,14 +17,6 @@ type EntryStatus = Bool
-- amtWidth = 11 -- amtWidth = 11
-- balWidth = 12 -- balWidth = 12
data Entry = Entry {
edate :: Date,
estatus :: EntryStatus,
ecode :: String,
edescription :: String,
etransactions :: [Transaction]
} deriving (Eq)
instance Show Entry where show = showEntry instance Show Entry where show = showEntry
showEntry e = (showDate $ edate e) ++ " " ++ (showDescription $ edescription e) ++ " " showEntry e = (showDate $ edate e) ++ " " ++ (showDescription $ edescription e) ++ " "
@ -43,19 +33,9 @@ autofillEntry e =
-- modifier & periodic entries -- modifier & periodic entries
data ModifierEntry = ModifierEntry { -- aka "automated entry"
valueexpr :: String,
m_transactions :: [Transaction]
} deriving (Eq)
instance Show ModifierEntry where instance Show ModifierEntry where
show e = "= " ++ (valueexpr e) ++ "\n" ++ unlines (map show (m_transactions e)) show e = "= " ++ (valueexpr e) ++ "\n" ++ unlines (map show (m_transactions e))
data PeriodicEntry = PeriodicEntry {
periodexpr :: String,
p_transactions :: [Transaction]
} deriving (Eq)
instance Show PeriodicEntry where instance Show PeriodicEntry where
show e = "~ " ++ (periodexpr e) ++ "\n" ++ unlines (map show (p_transactions e)) show e = "~ " ++ (periodexpr e) ++ "\n" ++ unlines (map show (p_transactions e))

View File

@ -6,6 +6,7 @@ import Types
import Entry import Entry
import Transaction import Transaction
import Amount import Amount
import Currency
-- We convert Transactions into EntryTransactions, which are (entry, -- We convert Transactions into EntryTransactions, which are (entry,
@ -13,8 +14,6 @@ import Amount
-- reference their entry like in OO. These are referred to as just -- reference their entry like in OO. These are referred to as just
-- "transactions" in code above. -- "transactions" in code above.
type EntryTransaction = (Entry,Transaction)
entry (e,t) = e entry (e,t) = e
transaction (e,t) = t transaction (e,t) = t
date (e,t) = edate e date (e,t) = edate e

View File

@ -9,12 +9,6 @@ import Entry
import EntryTransaction import EntryTransaction
data Ledger = Ledger {
modifier_entries :: [ModifierEntry],
periodic_entries :: [PeriodicEntry],
entries :: [Entry]
} deriving (Eq)
instance Show Ledger where instance Show Ledger where
show l = printf "Ledger with %d entries" show l = printf "Ledger with %d entries"
((length $ entries l) + ((length $ entries l) +

View File

@ -22,7 +22,7 @@ haddock:
haddock -h -o doc *.hs haddock -h -o doc *.hs
overview: overview:
@./overview.hs hledger.hs @./overview.hs Types.hs
loc: loc:
@darcs trackdown 'find . -name "*hs" |xargs wc -l |echo OUTPUT `tail -1`; false' |ruby -nae'puts $$F[1] if /^OUTPUT/' @darcs trackdown 'find . -name "*hs" |xargs wc -l |echo OUTPUT `tail -1`; false' |ruby -nae'puts $$F[1] if /^OUTPUT/'

View File

@ -1,6 +1,7 @@
-- data types & behaviours -- all data types & behaviours
module Models ( module Models (
module Types, module Types,
module Currency,
module Amount, module Amount,
module AccountName, module AccountName,
module Transaction, module Transaction,
@ -14,6 +15,7 @@ where
import qualified Data.Map as Map import qualified Data.Map as Map
import Types import Types
import Currency
import Amount import Amount
import AccountName import AccountName
import Transaction import Transaction

View File

@ -2,24 +2,15 @@ module TimeLog
where where
import Utils import Utils
import Types import Types
import Currency
import Amount import Amount
import Transaction import Transaction
import Entry import Entry
import Ledger import Ledger
data TimeLogEntry = TimeLogEntry {
tcode :: Char,
tdatetime :: DateTime,
tcomment :: String
} deriving (Eq,Ord)
instance Show TimeLogEntry where instance Show TimeLogEntry where
show t = printf "%s %s %s" (show $ tcode t) (tdatetime t) (tcomment t) show t = printf "%s %s %s" (show $ tcode t) (tdatetime t) (tcomment t)
data TimeLog = TimeLog {
timelog_entries :: [TimeLogEntry]
} deriving (Eq)
instance Show TimeLog where instance Show TimeLog where
show tl = printf "TimeLog with %d entries" $ length $ timelog_entries tl show tl = printf "TimeLog with %d entries" $ length $ timelog_entries tl

View File

@ -7,11 +7,6 @@ import AccountName
import Amount import Amount
data Transaction = Transaction {
taccount :: AccountName,
tamount :: Amount
} deriving (Eq)
instance Show Transaction where show = showTransaction instance Show Transaction where show = showTransaction
showTransaction t = (showAccountName $ taccount t) ++ " " ++ (showAmount $ tamount t) showTransaction t = (showAccountName $ taccount t) ++ " " ++ (showAmount $ tamount t)

115
Types.hs
View File

@ -2,6 +2,121 @@ module Types
where where
import Utils import Utils
{-
First, here is the module hierarchy. The initial implementation defined
types in each module and so was strictly layered. Now, all types have been
moved to the bottom, with modules still used to group related functions
(aka methods - "make overview" to list these).
hledger
Options
Tests
Parse
Models
TimeLog
TimeLogEntry
Account
Ledger
EntryTransaction
Entry
Transaction
AccountName
Amount
Currency
Types
Utils
(Will this allow a more muddled design ? Possibly, though starting out
layered probably helped, but note previous comment:
Each layer can only reference things below it. A seeming problem:
CookedLedger must be at the top so it can cache any of the others. Code
below it can not use its fast functions, and code above it should use
only its functions for good performance. Upper-level code loses the
benefit of many lower-level functions and has to reimplement them as
fast versions.)
-}
type Date = String type Date = String
type DateTime = String type DateTime = String
data Currency = Currency {
symbol :: String,
rate :: Double -- relative to the dollar
} deriving (Eq,Show)
-- some amount of money, time, stock, oranges, etc.
data Amount = Amount {
currency :: Currency,
quantity :: Double
} deriving (Eq)
-- AccountNames are strings like "assets:cash:petty"; from these we build
-- the chart of accounts, which should be a simple hierarchy.
type AccountName = String
-- a flow of an amount to an account
data Transaction = Transaction {
taccount :: AccountName,
tamount :: Amount
} deriving (Eq)
-- cleared ?
type EntryStatus = Bool
-- a ledger entry, with two or more balanced transactions
data Entry = Entry {
edate :: Date,
estatus :: EntryStatus,
ecode :: String,
edescription :: String,
etransactions :: [Transaction]
} deriving (Eq)
-- an "automated" entry (see = in ledger manual)
data ModifierEntry = ModifierEntry {
valueexpr :: String,
m_transactions :: [Transaction]
} deriving (Eq)
-- a periodic entry (see ~ in ledger manual)
data PeriodicEntry = PeriodicEntry {
periodexpr :: String,
p_transactions :: [Transaction]
} deriving (Eq)
-- a parsed ledger file
data Ledger = Ledger {
modifier_entries :: [ModifierEntry],
periodic_entries :: [PeriodicEntry],
entries :: [Entry]
} deriving (Eq)
-- we also process timeclock.el's timelogs
data TimeLogEntry = TimeLogEntry {
tcode :: Char,
tdatetime :: DateTime,
tcomment :: String
} deriving (Eq,Ord)
data TimeLog = TimeLog {
timelog_entries :: [TimeLogEntry]
} deriving (Eq)
-- We convert Transactions into EntryTransactions, which are (entry,
-- transaction) pairs, since I couldn't see how to have transactions
-- reference their entry like in OO. These are referred to as just
-- "transactions" in modules above EntryTransaction.
type EntryTransaction = (Entry,Transaction)
-- an Account caches a particular account's name, balance and transactions
-- from a Ledger
data Account = Account {
aname :: AccountName,
atransactions :: [EntryTransaction], -- excludes sub-accounts
abalance :: Amount -- includes sub-accounts
}

View File

@ -26,9 +26,6 @@ splitAtElement e l =
where where
(first,rest) = break (e==) l' (first,rest) = break (e==) l'
-- testing support
-- tree tools -- tree tools
root = rootLabel root = rootLabel
@ -37,8 +34,7 @@ branches = subForest
-- remove all nodes past a certain depth -- remove all nodes past a certain depth
treeprune :: Int -> Tree a -> Tree a treeprune :: Int -> Tree a -> Tree a
treeprune 0 t = Node (root t) [] treeprune 0 t = Node (root t) []
treeprune d t = treeprune d t = Node (root t) (map (treeprune $ d-1) $ branches t)
Node (root t) (map (treeprune $ d-1) $ branches t)
-- apply f to all tree nodes -- apply f to all tree nodes
treemap :: (a -> b) -> Tree a -> Tree b treemap :: (a -> b) -> Tree a -> Tree b
@ -57,4 +53,9 @@ treeany f t = (f $ root t) || (any (treeany f) $ branches t)
-- treedrop -- remove the leaves which do fulfill predicate. -- treedrop -- remove the leaves which do fulfill predicate.
-- treedropall -- do this repeatedly. -- treedropall -- do this repeatedly.
strace a = trace (show a) a -- debugging
strace a = trace (show a) a
-- testing

View File

@ -4,25 +4,7 @@ hledger - ledger-compatible money management tool (& haskell study)
GPLv3, (c) Simon Michael & contributors GPLv3, (c) Simon Michael & contributors
A port of John Wiegley's ledger at http://newartisans.com/ledger.html A port of John Wiegley's ledger at http://newartisans.com/ledger.html
Here is a rough overview of the module/model hierarchy: See Types.hs for a code overview.
hledger
Options
Tests
Parse
Models
TimeLog
TimeLogEntry
Account
Ledger
EntryTransaction
Entry
Transaction
AccountName
Amount
Types
Utils
-} -}
module Main module Main