move the rest of the core code to the Ledger package

This commit is contained in:
Simon Michael 2008-10-03 00:40:06 +00:00
parent 3bca3cfa0f
commit c699b979f8
16 changed files with 89 additions and 89 deletions

View File

@ -1,12 +1,12 @@
module Account module Ledger.Account
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import AccountName import Ledger.AccountName
import Amount import Ledger.Amount
import LedgerEntry import Ledger.LedgerEntry
import RawTransaction import Ledger.RawTransaction
import Transaction import Ledger.Transaction
instance Show Account where instance Show Account where

View File

@ -1,4 +1,4 @@
module AccountName module Ledger.AccountName
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types

View File

@ -34,7 +34,7 @@ currencies can be converted to a simple amount. Arithmetic examples:
@ @
-} -}
module Amount module Ledger.Amount
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types

View File

@ -1,15 +1,15 @@
module Ledger module Ledger.Ledger
where where
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Map ((!)) import Data.Map ((!))
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Amount import Ledger.Amount
import Account import Ledger.Account
import AccountName import Ledger.AccountName
import Transaction import Ledger.Transaction
import RawLedger import Ledger.RawLedger
import LedgerEntry import Ledger.LedgerEntry
rawLedgerTransactions :: RawLedger -> [Transaction] rawLedgerTransactions :: RawLedger -> [Transaction]

View File

@ -1,9 +1,9 @@
module LedgerEntry module Ledger.LedgerEntry
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import RawTransaction import Ledger.RawTransaction
import Amount import Ledger.Amount
instance Show LedgerEntry where show = showEntryDescription instance Show LedgerEntry where show = showEntryDescription

32
Ledger/Models.hs Normal file
View File

@ -0,0 +1,32 @@
{-|
This module makes it easier to import all the hledger "models",
the main data types and their "methods".
-}
module Ledger.Models (
module Ledger.Types,
module Ledger.Currency,
module Ledger.Amount,
module Ledger.AccountName,
module Ledger.RawTransaction,
module Ledger.LedgerEntry,
module Ledger.TimeLog,
module Ledger.Transaction,
-- module Ledger.RawLedger,
module Ledger.Account,
module Ledger.Ledger,
)
where
import qualified Data.Map as Map
import Ledger.Types
import Ledger.Currency
import Ledger.Amount
import Ledger.AccountName
import Ledger.RawTransaction
import Ledger.LedgerEntry
import Ledger.TimeLog
import Ledger.Transaction
import Ledger.RawLedger
import Ledger.Account
import Ledger.Ledger

View File

@ -101,7 +101,7 @@ i, o, b, h
See Tests.hs for sample data. See Tests.hs for sample data.
-} -}
module Parse module Ledger.Parse
where where
import qualified Data.Map as Map import qualified Data.Map as Map
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
@ -110,21 +110,10 @@ import qualified Text.ParserCombinators.Parsec.Token as P
import System.IO import System.IO
import Ledger.Utils import Ledger.Utils
import Models import Ledger.Models
import Options
-- utils -- utils
-- | parse the user's specified ledger file and do some action with it
-- (or report a parse error)
parseLedgerAndDo :: [Flag] -> (Regex,Regex) -> (Ledger -> IO ()) -> IO ()
parseLedgerAndDo opts pats cmd = do
path <- ledgerFilePath opts
parsed <- parseLedgerFile path
case parsed of Left err -> parseError err
Right l -> cmd $ cacheLedger l pats
parseLedgerFile :: String -> IO (Either ParseError RawLedger) 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

View File

@ -1,11 +1,11 @@
module RawLedger module Ledger.RawLedger
where where
import qualified Data.Map as Map import qualified Data.Map as Map
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import AccountName import Ledger.AccountName
import LedgerEntry import Ledger.LedgerEntry
instance Show RawLedger where instance Show RawLedger where

View File

@ -1,9 +1,9 @@
module RawTransaction module Ledger.RawTransaction
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import AccountName import Ledger.AccountName
import Amount import Ledger.Amount
instance Show RawTransaction where show = showLedgerTransaction instance Show RawTransaction where show = showLedgerTransaction

View File

@ -1,12 +1,12 @@
module TimeLog module Ledger.TimeLog
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Currency import Ledger.Currency
import Amount import Ledger.Amount
import RawTransaction import Ledger.RawTransaction
import LedgerEntry import Ledger.LedgerEntry
import RawLedger import Ledger.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)

View File

@ -1,12 +1,12 @@
module Transaction module Ledger.Transaction
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import AccountName import Ledger.AccountName
import LedgerEntry import Ledger.LedgerEntry
import RawTransaction import Ledger.RawTransaction
import Amount import Ledger.Amount
import Currency import Ledger.Currency
instance Show Transaction where instance Show Transaction where

View File

@ -1,4 +1,4 @@
-- standard 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

@ -1,32 +0,0 @@
{-|
This module makes it easier to import all the hledger "models",
the main data types and their "methods".
-}
module Models (
module Ledger.Types,
module Currency,
module Amount,
module AccountName,
module RawTransaction,
module LedgerEntry,
module TimeLog,
module Transaction,
-- module RawLedger,
module Account,
module Ledger,
)
where
import qualified Data.Map as Map
import Ledger.Types
import Currency
import Amount
import AccountName
import RawTransaction
import LedgerEntry
import TimeLog
import Transaction
import RawLedger
import Account
import Ledger

View File

@ -1,4 +1,4 @@
module Options (parseOptions, parsePatternArgs, wildcard, Flag(..), usage, ledgerFilePath) module Options (parseOptions, parsePatternArgs, wildcard, Flag(..), usage, ledgerFilePath, parseLedgerAndDo)
where where
import System.Console.GetOpt import System.Console.GetOpt
import System.Directory import System.Directory
@ -7,6 +7,8 @@ import Data.Maybe (fromMaybe)
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Ledger.Parse (parseLedgerFile, parseError)
import Ledger.Ledger (cacheLedger)
usagehdr = "Usage: hledger [OPTIONS] "++commands++" [ACCTPATTERNS] [-- DESCPATTERNS]\nOptions:" usagehdr = "Usage: hledger [OPTIONS] "++commands++" [ACCTPATTERNS] [-- DESCPATTERNS]\nOptions:"
@ -88,4 +90,14 @@ regexFor [] = wildcard
regexFor ss = mkRegex $ "(" ++ (unwords $ intersperse "|" ss) ++ ")" regexFor ss = mkRegex $ "(" ++ (unwords $ intersperse "|" ss) ++ ")"
wildcard :: Regex wildcard :: Regex
wildcard = mkRegex ".*" wildcard = mkRegex ".*"
-- | parse the user's specified ledger file and do some action with it
-- (or report a parse error)
parseLedgerAndDo :: [Flag] -> (Regex,Regex) -> (Ledger -> IO ()) -> IO ()
parseLedgerAndDo opts pats cmd = do
path <- ledgerFilePath opts
parsed <- parseLedgerFile path
case parsed of Left err -> parseError err
Right l -> cmd $ cacheLedger l pats

View File

@ -4,8 +4,8 @@ import qualified Data.Map as Map
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import Options import Options
import Models import Ledger.Models
import Parse import Ledger.Parse
import Ledger.Utils import Ledger.Utils
-- utils -- utils

View File

@ -59,13 +59,12 @@ This module includes some helpers for querying your ledger in ghci. Examples:
module Main module Main
where where
import System import System
import Text.ParserCombinators.Parsec (ParseError)
import qualified Data.Map as Map (lookup) import qualified Data.Map as Map (lookup)
import Options import Options
import Models
import Parse (parseLedgerAndDo, parseLedgerFile)
import Tests (hunit, quickcheck) import Tests (hunit, quickcheck)
import Ledger.Models
import Ledger.Parse (parseLedgerFile)
import Ledger.Utils hiding (test) import Ledger.Utils hiding (test)