diff --git a/Account.hs b/Ledger/Account.hs similarity index 56% rename from Account.hs rename to Ledger/Account.hs index ba54fd335..4b365fd6b 100644 --- a/Account.hs +++ b/Ledger/Account.hs @@ -1,12 +1,12 @@ -module Account +module Ledger.Account where import Ledger.Utils import Ledger.Types -import AccountName -import Amount -import LedgerEntry -import RawTransaction -import Transaction +import Ledger.AccountName +import Ledger.Amount +import Ledger.LedgerEntry +import Ledger.RawTransaction +import Ledger.Transaction instance Show Account where diff --git a/AccountName.hs b/Ledger/AccountName.hs similarity index 99% rename from AccountName.hs rename to Ledger/AccountName.hs index 2061f38e9..a85c97bc6 100644 --- a/AccountName.hs +++ b/Ledger/AccountName.hs @@ -1,4 +1,4 @@ -module AccountName +module Ledger.AccountName where import Ledger.Utils import Ledger.Types diff --git a/Amount.hs b/Ledger/Amount.hs similarity index 99% rename from Amount.hs rename to Ledger/Amount.hs index 9434bd292..cdf39fd31 100644 --- a/Amount.hs +++ b/Ledger/Amount.hs @@ -34,7 +34,7 @@ currencies can be converted to a simple amount. Arithmetic examples: @ -} -module Amount +module Ledger.Amount where import Ledger.Utils import Ledger.Types diff --git a/Ledger.hs b/Ledger/Ledger.hs similarity index 97% rename from Ledger.hs rename to Ledger/Ledger.hs index 0a6944f32..35b94f451 100644 --- a/Ledger.hs +++ b/Ledger/Ledger.hs @@ -1,15 +1,15 @@ -module Ledger +module Ledger.Ledger where import qualified Data.Map as Map import Data.Map ((!)) import Ledger.Utils import Ledger.Types -import Amount -import Account -import AccountName -import Transaction -import RawLedger -import LedgerEntry +import Ledger.Amount +import Ledger.Account +import Ledger.AccountName +import Ledger.Transaction +import Ledger.RawLedger +import Ledger.LedgerEntry rawLedgerTransactions :: RawLedger -> [Transaction] diff --git a/LedgerEntry.hs b/Ledger/LedgerEntry.hs similarity index 97% rename from LedgerEntry.hs rename to Ledger/LedgerEntry.hs index 73c06696d..937c95096 100644 --- a/LedgerEntry.hs +++ b/Ledger/LedgerEntry.hs @@ -1,9 +1,9 @@ -module LedgerEntry +module Ledger.LedgerEntry where import Ledger.Utils import Ledger.Types -import RawTransaction -import Amount +import Ledger.RawTransaction +import Ledger.Amount instance Show LedgerEntry where show = showEntryDescription diff --git a/Ledger/Models.hs b/Ledger/Models.hs new file mode 100644 index 000000000..c376b1ffd --- /dev/null +++ b/Ledger/Models.hs @@ -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 + diff --git a/Parse.hs b/Ledger/Parse.hs similarity index 96% rename from Parse.hs rename to Ledger/Parse.hs index 91dcafbfa..3e7e83d42 100644 --- a/Parse.hs +++ b/Ledger/Parse.hs @@ -101,7 +101,7 @@ i, o, b, h See Tests.hs for sample data. -} -module Parse +module Ledger.Parse where import qualified Data.Map as Map import Text.ParserCombinators.Parsec @@ -110,21 +110,10 @@ import qualified Text.ParserCombinators.Parsec.Token as P import System.IO import Ledger.Utils -import Models -import Options - +import Ledger.Models -- 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 "-" = fmap (parse ledgerfile "-") $ hGetContents stdin parseLedgerFile f = parseFromFile ledgerfile f diff --git a/RawLedger.hs b/Ledger/RawLedger.hs similarity index 79% rename from RawLedger.hs rename to Ledger/RawLedger.hs index 2ce82d7ba..89eac41b5 100644 --- a/RawLedger.hs +++ b/Ledger/RawLedger.hs @@ -1,11 +1,11 @@ -module RawLedger +module Ledger.RawLedger where import qualified Data.Map as Map import Ledger.Utils import Ledger.Types -import AccountName -import LedgerEntry +import Ledger.AccountName +import Ledger.LedgerEntry instance Show RawLedger where diff --git a/RawTransaction.hs b/Ledger/RawTransaction.hs similarity index 93% rename from RawTransaction.hs rename to Ledger/RawTransaction.hs index 12a657582..aa01f3dc4 100644 --- a/RawTransaction.hs +++ b/Ledger/RawTransaction.hs @@ -1,9 +1,9 @@ -module RawTransaction +module Ledger.RawTransaction where import Ledger.Utils import Ledger.Types -import AccountName -import Amount +import Ledger.AccountName +import Ledger.Amount instance Show RawTransaction where show = showLedgerTransaction diff --git a/TimeLog.hs b/Ledger/TimeLog.hs similarity index 90% rename from TimeLog.hs rename to Ledger/TimeLog.hs index d63c67418..669bf60c5 100644 --- a/TimeLog.hs +++ b/Ledger/TimeLog.hs @@ -1,12 +1,12 @@ -module TimeLog +module Ledger.TimeLog where import Ledger.Utils import Ledger.Types -import Currency -import Amount -import RawTransaction -import LedgerEntry -import RawLedger +import Ledger.Currency +import Ledger.Amount +import Ledger.RawTransaction +import Ledger.LedgerEntry +import Ledger.RawLedger instance Show TimeLogEntry where show t = printf "%s %s %s" (show $ tlcode t) (tldatetime t) (tlcomment t) diff --git a/Transaction.hs b/Ledger/Transaction.hs similarity index 93% rename from Transaction.hs rename to Ledger/Transaction.hs index e3e4ce241..901a9aa0f 100644 --- a/Transaction.hs +++ b/Ledger/Transaction.hs @@ -1,12 +1,12 @@ -module Transaction +module Ledger.Transaction where import Ledger.Utils import Ledger.Types -import AccountName -import LedgerEntry -import RawTransaction -import Amount -import Currency +import Ledger.AccountName +import Ledger.LedgerEntry +import Ledger.RawTransaction +import Ledger.Amount +import Ledger.Currency instance Show Transaction where diff --git a/Ledger/Utils.hs b/Ledger/Utils.hs index 527ee6f63..b0f6a5469 100644 --- a/Ledger/Utils.hs +++ b/Ledger/Utils.hs @@ -1,4 +1,4 @@ --- standard imports and utilities +-- standard always-available imports and utilities module Ledger.Utils ( module Ledger.Utils, module Char, diff --git a/Models.hs b/Models.hs deleted file mode 100644 index beb18a6df..000000000 --- a/Models.hs +++ /dev/null @@ -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 - diff --git a/Options.hs b/Options.hs index 41b5efda7..df149cb6e 100644 --- a/Options.hs +++ b/Options.hs @@ -1,4 +1,4 @@ -module Options (parseOptions, parsePatternArgs, wildcard, Flag(..), usage, ledgerFilePath) +module Options (parseOptions, parsePatternArgs, wildcard, Flag(..), usage, ledgerFilePath, parseLedgerAndDo) where import System.Console.GetOpt import System.Directory @@ -7,6 +7,8 @@ import Data.Maybe (fromMaybe) import Ledger.Utils import Ledger.Types +import Ledger.Parse (parseLedgerFile, parseError) +import Ledger.Ledger (cacheLedger) usagehdr = "Usage: hledger [OPTIONS] "++commands++" [ACCTPATTERNS] [-- DESCPATTERNS]\nOptions:" @@ -88,4 +90,14 @@ regexFor [] = wildcard regexFor ss = mkRegex $ "(" ++ (unwords $ intersperse "|" ss) ++ ")" wildcard :: Regex -wildcard = mkRegex ".*" \ No newline at end of file +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 + diff --git a/Tests.hs b/Tests.hs index a75171eee..8b26a430d 100644 --- a/Tests.hs +++ b/Tests.hs @@ -4,8 +4,8 @@ import qualified Data.Map as Map import Text.ParserCombinators.Parsec import Options -import Models -import Parse +import Ledger.Models +import Ledger.Parse import Ledger.Utils -- utils diff --git a/hledger.hs b/hledger.hs index e3f1da394..e22c70bf6 100644 --- a/hledger.hs +++ b/hledger.hs @@ -59,13 +59,12 @@ This module includes some helpers for querying your ledger in ghci. Examples: module Main where import System -import Text.ParserCombinators.Parsec (ParseError) import qualified Data.Map as Map (lookup) import Options -import Models -import Parse (parseLedgerAndDo, parseLedgerFile) import Tests (hunit, quickcheck) +import Ledger.Models +import Ledger.Parse (parseLedgerFile) import Ledger.Utils hiding (test)