rename LedgerFile to RawLedger
This commit is contained in:
parent
29b75f3949
commit
f4b4fc98fe
24
Ledger.hs
24
Ledger.hs
@ -8,22 +8,22 @@ import Amount
|
|||||||
import Account
|
import Account
|
||||||
import AccountName
|
import AccountName
|
||||||
import Transaction
|
import Transaction
|
||||||
import LedgerFile
|
import RawLedger
|
||||||
|
|
||||||
|
|
||||||
rawLedgerTransactions :: LedgerFile -> [Transaction]
|
rawLedgerTransactions :: RawLedger -> [Transaction]
|
||||||
rawLedgerTransactions = txns . entries
|
rawLedgerTransactions = txns . entries
|
||||||
where
|
where
|
||||||
txns :: [LedgerEntry] -> [Transaction]
|
txns :: [LedgerEntry] -> [Transaction]
|
||||||
txns es = concat $ map flattenEntry $ zip es (iterate (+1) 1)
|
txns es = concat $ map flattenEntry $ zip es (iterate (+1) 1)
|
||||||
|
|
||||||
rawLedgerAccountNamesUsed :: LedgerFile -> [AccountName]
|
rawLedgerAccountNamesUsed :: RawLedger -> [AccountName]
|
||||||
rawLedgerAccountNamesUsed = accountNamesFromTransactions . rawLedgerTransactions
|
rawLedgerAccountNamesUsed = accountNamesFromTransactions . rawLedgerTransactions
|
||||||
|
|
||||||
rawLedgerAccountNames :: LedgerFile -> [AccountName]
|
rawLedgerAccountNames :: RawLedger -> [AccountName]
|
||||||
rawLedgerAccountNames = sort . expandAccountNames . rawLedgerAccountNamesUsed
|
rawLedgerAccountNames = sort . expandAccountNames . rawLedgerAccountNamesUsed
|
||||||
|
|
||||||
rawLedgerAccountNameTree :: LedgerFile -> Tree AccountName
|
rawLedgerAccountNameTree :: RawLedger -> Tree AccountName
|
||||||
rawLedgerAccountNameTree l = accountNameTreeFrom $ rawLedgerAccountNames l
|
rawLedgerAccountNameTree l = accountNameTreeFrom $ rawLedgerAccountNames l
|
||||||
|
|
||||||
|
|
||||||
@ -38,7 +38,7 @@ instance Show Ledger where
|
|||||||
-- 1. filter based on account/description patterns, if any
|
-- 1. filter based on account/description patterns, if any
|
||||||
-- 2. cache per-account info
|
-- 2. cache per-account info
|
||||||
-- 3. figure out the precision(s) to use
|
-- 3. figure out the precision(s) to use
|
||||||
cacheLedger :: LedgerFile -> (Regex,Regex) -> Ledger
|
cacheLedger :: RawLedger -> (Regex,Regex) -> Ledger
|
||||||
cacheLedger l pats =
|
cacheLedger l pats =
|
||||||
let
|
let
|
||||||
lprecision = maximum $ map (precision . amount) $ rawLedgerTransactions l
|
lprecision = maximum $ map (precision . amount) $ rawLedgerTransactions l
|
||||||
@ -66,9 +66,9 @@ cacheLedger l pats =
|
|||||||
-- description patterns, if any, and which have at least one
|
-- description patterns, if any, and which have at least one
|
||||||
-- transaction matching one of the account patterns, if any.
|
-- transaction matching one of the account patterns, if any.
|
||||||
-- No description or account patterns implies match all.
|
-- No description or account patterns implies match all.
|
||||||
filterLedgerEntries :: (Regex,Regex) -> LedgerFile -> LedgerFile
|
filterLedgerEntries :: (Regex,Regex) -> RawLedger -> RawLedger
|
||||||
filterLedgerEntries (acctpat,descpat) (LedgerFile ms ps es f) =
|
filterLedgerEntries (acctpat,descpat) (RawLedger ms ps es f) =
|
||||||
LedgerFile ms ps filteredentries f
|
RawLedger ms ps filteredentries f
|
||||||
where
|
where
|
||||||
filteredentries :: [LedgerEntry]
|
filteredentries :: [LedgerEntry]
|
||||||
filteredentries = (filter matchdesc $ filter (any matchtxn . etransactions) es)
|
filteredentries = (filter matchdesc $ filter (any matchtxn . etransactions) es)
|
||||||
@ -84,9 +84,9 @@ filterLedgerEntries (acctpat,descpat) (LedgerFile ms ps es f) =
|
|||||||
-- | in each ledger entry, filter out transactions which do not match
|
-- | in each ledger entry, filter out transactions which do not match
|
||||||
-- the account patterns, if any. (Entries are no longer balanced
|
-- the account patterns, if any. (Entries are no longer balanced
|
||||||
-- after this.)
|
-- after this.)
|
||||||
filterLedgerTransactions :: (Regex,Regex) -> LedgerFile -> LedgerFile
|
filterLedgerTransactions :: (Regex,Regex) -> RawLedger -> RawLedger
|
||||||
filterLedgerTransactions (acctpat,descpat) (LedgerFile ms ps es f) =
|
filterLedgerTransactions (acctpat,descpat) (RawLedger ms ps es f) =
|
||||||
LedgerFile ms ps (map filterentrytxns es) f
|
RawLedger ms ps (map filterentrytxns es) f
|
||||||
where
|
where
|
||||||
filterentrytxns l@(LedgerEntry _ _ _ _ _ ts _) = l{etransactions=filter matchtxn ts}
|
filterentrytxns l@(LedgerEntry _ _ _ _ _ ts _) = l{etransactions=filter matchtxn ts}
|
||||||
matchtxn t = case matchRegex acctpat (taccount t) of
|
matchtxn t = case matchRegex acctpat (taccount t) of
|
||||||
|
|||||||
@ -8,7 +8,7 @@ module Models (
|
|||||||
module LedgerEntry,
|
module LedgerEntry,
|
||||||
module TimeLog,
|
module TimeLog,
|
||||||
module Transaction,
|
module Transaction,
|
||||||
-- module LedgerFile,
|
-- module RawLedger,
|
||||||
module Account,
|
module Account,
|
||||||
module Ledger,
|
module Ledger,
|
||||||
)
|
)
|
||||||
@ -23,7 +23,7 @@ import LedgerTransaction
|
|||||||
import LedgerEntry
|
import LedgerEntry
|
||||||
import TimeLog
|
import TimeLog
|
||||||
import Transaction
|
import Transaction
|
||||||
import LedgerFile
|
import RawLedger
|
||||||
import Account
|
import Account
|
||||||
import Ledger
|
import Ledger
|
||||||
|
|
||||||
|
|||||||
10
Parse.hs
10
Parse.hs
@ -125,7 +125,7 @@ parseLedgerAndDo opts pats cmd = do
|
|||||||
case parsed of Left err -> parseError err
|
case parsed of Left err -> parseError err
|
||||||
Right l -> cmd $ cacheLedger l pats
|
Right l -> cmd $ cacheLedger l pats
|
||||||
|
|
||||||
parseLedgerFile :: String -> IO (Either ParseError LedgerFile)
|
parseLedgerFile :: String -> IO (Either ParseError RawLedger)
|
||||||
parseLedgerFile "-" = fmap (parse ledgerfile "-") $ hGetContents stdin
|
parseLedgerFile "-" = fmap (parse ledgerfile "-") $ hGetContents stdin
|
||||||
parseLedgerFile f = parseFromFile ledgerfile f
|
parseLedgerFile f = parseFromFile ledgerfile f
|
||||||
|
|
||||||
@ -159,10 +159,10 @@ reservedOp = P.reservedOp lexer
|
|||||||
|
|
||||||
-- parsers
|
-- parsers
|
||||||
|
|
||||||
ledgerfile :: Parser LedgerFile
|
ledgerfile :: Parser RawLedger
|
||||||
ledgerfile = ledger <|> ledgerfromtimelog
|
ledgerfile = ledger <|> ledgerfromtimelog
|
||||||
|
|
||||||
ledger :: Parser LedgerFile
|
ledger :: Parser RawLedger
|
||||||
ledger = do
|
ledger = do
|
||||||
-- for now these must come first, unlike ledger
|
-- for now these must come first, unlike ledger
|
||||||
modifier_entries <- many ledgermodifierentry
|
modifier_entries <- many ledgermodifierentry
|
||||||
@ -171,7 +171,7 @@ ledger = do
|
|||||||
entries <- (many ledgerentry) <?> "entry"
|
entries <- (many ledgerentry) <?> "entry"
|
||||||
final_comment_lines <- ledgernondatalines
|
final_comment_lines <- ledgernondatalines
|
||||||
eof
|
eof
|
||||||
return $ LedgerFile modifier_entries periodic_entries entries (unlines final_comment_lines)
|
return $ RawLedger modifier_entries periodic_entries entries (unlines final_comment_lines)
|
||||||
|
|
||||||
ledgernondatalines :: Parser [String]
|
ledgernondatalines :: Parser [String]
|
||||||
ledgernondatalines = many (ledgerdirective <|> -- treat as comments
|
ledgernondatalines = many (ledgerdirective <|> -- treat as comments
|
||||||
@ -331,7 +331,7 @@ o 2007/03/10 17:26:02
|
|||||||
@
|
@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
ledgerfromtimelog :: Parser LedgerFile
|
ledgerfromtimelog :: Parser RawLedger
|
||||||
ledgerfromtimelog = do
|
ledgerfromtimelog = do
|
||||||
tl <- timelog
|
tl <- timelog
|
||||||
return $ ledgerFromTimeLog tl
|
return $ ledgerFromTimeLog tl
|
||||||
|
|||||||
@ -1,4 +1,4 @@
|
|||||||
module LedgerFile
|
module RawLedger
|
||||||
where
|
where
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
|
|
||||||
@ -8,8 +8,8 @@ import AccountName
|
|||||||
import LedgerEntry
|
import LedgerEntry
|
||||||
|
|
||||||
|
|
||||||
instance Show LedgerFile where
|
instance Show RawLedger where
|
||||||
show l = printf "LedgerFile with %d entries"
|
show l = printf "RawLedger with %d entries"
|
||||||
((length $ entries l) +
|
((length $ entries l) +
|
||||||
(length $ modifier_entries l) +
|
(length $ modifier_entries l) +
|
||||||
(length $ periodic_entries l))
|
(length $ periodic_entries l))
|
||||||
2
Tests.hs
2
Tests.hs
@ -200,7 +200,7 @@ ledger7_str = "\
|
|||||||
\ assets:checking \n\
|
\ assets:checking \n\
|
||||||
\\n" --"
|
\\n" --"
|
||||||
|
|
||||||
ledger7 = LedgerFile
|
ledger7 = RawLedger
|
||||||
[]
|
[]
|
||||||
[]
|
[]
|
||||||
[
|
[
|
||||||
|
|||||||
@ -6,7 +6,7 @@ import Currency
|
|||||||
import Amount
|
import Amount
|
||||||
import LedgerTransaction
|
import LedgerTransaction
|
||||||
import LedgerEntry
|
import LedgerEntry
|
||||||
import LedgerFile
|
import RawLedger
|
||||||
|
|
||||||
instance Show TimeLogEntry where
|
instance Show TimeLogEntry where
|
||||||
show t = printf "%s %s %s" (show $ tlcode t) (tldatetime t) (tlcomment t)
|
show t = printf "%s %s %s" (show $ tlcode t) (tldatetime t) (tlcomment t)
|
||||||
@ -14,9 +14,9 @@ instance Show TimeLogEntry where
|
|||||||
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
|
||||||
|
|
||||||
ledgerFromTimeLog :: TimeLog -> LedgerFile
|
ledgerFromTimeLog :: TimeLog -> RawLedger
|
||||||
ledgerFromTimeLog tl =
|
ledgerFromTimeLog tl =
|
||||||
LedgerFile [] [] (entriesFromTimeLogEntries $ timelog_entries tl) ""
|
RawLedger [] [] (entriesFromTimeLogEntries $ timelog_entries tl) ""
|
||||||
|
|
||||||
entriesFromTimeLogEntries :: [TimeLogEntry] -> [LedgerEntry]
|
entriesFromTimeLogEntries :: [TimeLogEntry] -> [LedgerEntry]
|
||||||
|
|
||||||
|
|||||||
4
Types.hs
4
Types.hs
@ -69,7 +69,7 @@ data TimeLog = TimeLog {
|
|||||||
} deriving (Eq)
|
} deriving (Eq)
|
||||||
|
|
||||||
-- | a parsed ledger file
|
-- | a parsed ledger file
|
||||||
data LedgerFile = LedgerFile {
|
data RawLedger = RawLedger {
|
||||||
modifier_entries :: [ModifierEntry],
|
modifier_entries :: [ModifierEntry],
|
||||||
periodic_entries :: [PeriodicEntry],
|
periodic_entries :: [PeriodicEntry],
|
||||||
entries :: [LedgerEntry],
|
entries :: [LedgerEntry],
|
||||||
@ -95,7 +95,7 @@ data Account = Account {
|
|||||||
|
|
||||||
-- | a ledger with account information cached for faster queries
|
-- | a ledger with account information cached for faster queries
|
||||||
data Ledger = Ledger {
|
data Ledger = Ledger {
|
||||||
rawledger :: LedgerFile,
|
rawledger :: RawLedger,
|
||||||
accountnametree :: Tree AccountName,
|
accountnametree :: Tree AccountName,
|
||||||
accounts :: Map.Map AccountName Account,
|
accounts :: Map.Map AccountName Account,
|
||||||
lprecision :: Int
|
lprecision :: Int
|
||||||
|
|||||||
@ -28,7 +28,7 @@ hledger ("Main")
|
|||||||
"Ledger"
|
"Ledger"
|
||||||
"Account"
|
"Account"
|
||||||
"Transaction"
|
"Transaction"
|
||||||
"LedgerFile"
|
"RawLedger"
|
||||||
"LedgerEntry"
|
"LedgerEntry"
|
||||||
"LedgerTransaction"
|
"LedgerTransaction"
|
||||||
"AccountName"
|
"AccountName"
|
||||||
@ -107,7 +107,7 @@ balance opts pats = do
|
|||||||
$ ghci hledger.hs
|
$ ghci hledger.hs
|
||||||
GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help
|
GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help
|
||||||
Loading package base ... linking ... done.
|
Loading package base ... linking ... done.
|
||||||
Ok, modules loaded: Utils, Main, Tests, Parse, Models, Ledger, LedgerFile, LedgerEntry, Amount, Currency, Types, LedgerTransaction, AccountName, Transaction, Account, TimeLog, Options.
|
Ok, modules loaded: Utils, Main, Tests, Parse, Models, Ledger, RawLedger, LedgerEntry, Amount, Currency, Types, LedgerTransaction, AccountName, Transaction, Account, TimeLog, Options.
|
||||||
Prelude Main> l <- myledger
|
Prelude Main> l <- myledger
|
||||||
<..snip..>
|
<..snip..>
|
||||||
Ledger with 628 entries, 128 accounts
|
Ledger with 628 entries, 128 accounts
|
||||||
@ -129,14 +129,14 @@ $ ghci hledger.hs
|
|||||||
myledger :: IO Ledger
|
myledger :: IO Ledger
|
||||||
myledger = do
|
myledger = do
|
||||||
parsed <- ledgerFilePath [] >>= parseLedgerFile
|
parsed <- ledgerFilePath [] >>= parseLedgerFile
|
||||||
let ledgerfile = either (\_ -> LedgerFile [] [] [] "") id parsed
|
let ledgerfile = either (\_ -> RawLedger [] [] [] "") id parsed
|
||||||
return $ cacheLedger ledgerfile (wildcard,wildcard)
|
return $ cacheLedger ledgerfile (wildcard,wildcard)
|
||||||
|
|
||||||
-- | return a Ledger parsed from the given file path
|
-- | return a Ledger parsed from the given file path
|
||||||
ledgerfromfile :: String -> IO Ledger
|
ledgerfromfile :: String -> IO Ledger
|
||||||
ledgerfromfile f = do
|
ledgerfromfile f = do
|
||||||
parsed <- ledgerFilePath [File f] >>= parseLedgerFile
|
parsed <- ledgerFilePath [File f] >>= parseLedgerFile
|
||||||
let ledgerfile = either (\_ -> LedgerFile [] [] [] "") id parsed
|
let ledgerfile = either (\_ -> RawLedger [] [] [] "") id parsed
|
||||||
return $ cacheLedger ledgerfile (wildcard,wildcard)
|
return $ cacheLedger ledgerfile (wildcard,wildcard)
|
||||||
|
|
||||||
accountnamed :: AccountName -> IO Account
|
accountnamed :: AccountName -> IO Account
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user