clean up imports whitespace, minimise explicit intra-app import/export declarations for now

This commit is contained in:
Simon Michael 2008-10-10 01:53:39 +00:00
parent 15ea00a327
commit cdc5a23192
11 changed files with 21 additions and 43 deletions

View File

@ -20,7 +20,6 @@ module Ledger (
)
where
import qualified Data.Map as Map
import Ledger.Types
import Ledger.Currency
import Ledger.Amount

View File

@ -42,6 +42,7 @@ import Ledger.Utils
import Ledger.Types
import Ledger.Currency
tests = runTestTT $ test [
show (dollars 1) ~?= "$1.00"
,show (hours 1) ~?= "1h" -- currently h1.00

View File

@ -8,22 +8,7 @@ providing the filtered entries & transactions.
-}
module Ledger.Ledger (
cacheLedger,
filterLedgerEntries,
accountnames,
ledgerAccount,
ledgerTransactions,
ledgerAccountTree,
addDataToAccountNameTree,
printentries,
printregister,
showLedgerAccountBalances,
showAccountTree,
isBoringInnerAccount,
isBoringInnerAccountName,
-- pruneBoringBranches,
)
module Ledger.Ledger
where
import qualified Data.Map as Map
import Data.Map ((!))

View File

@ -11,13 +11,13 @@ import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Language
import qualified Text.ParserCombinators.Parsec.Token as P
import System.IO
import Ledger.Utils
import Ledger.Types
import Ledger.Entry (autofillEntry)
import Ledger.Currency (getcurrency)
import Ledger.TimeLog (ledgerFromTimeLog)
-- utils
parseLedgerFile :: String -> IO (Either ParseError RawLedger)

View File

@ -8,7 +8,6 @@ the cached 'Ledger'.
module Ledger.RawLedger
where
import qualified Data.Map as Map
import Ledger.Utils
import Ledger.Types
import Ledger.AccountName

View File

@ -8,7 +8,6 @@ containing zero or more 'TimeLogEntry's. It can be converted to a
module Ledger.TimeLog
where
import Ledger.Utils
import Ledger.Types
import Ledger.Currency
@ -17,6 +16,7 @@ import Ledger.RawTransaction
import Ledger.Entry
import Ledger.RawLedger
instance Show TimeLogEntry where
show t = printf "%s %s %s" (show $ tlcode t) (tldatetime t) (tlcomment t)

View File

@ -10,6 +10,7 @@ where
import Ledger.Utils
import qualified Data.Map as Map
type Date = String
type DateTime = String

View File

@ -16,7 +16,9 @@ module Text.Regex,
module Debug.Trace,
module Test.QuickCheck,
module Test.HUnit,
defaultTimeLocale, UTCTime, diffUTCTime, parseTime, formatTime,
module System.Locale,
module Data.Time.Clock,
module Data.Time.Format
)
where
import Char

View File

@ -1,19 +1,10 @@
module Options (
Opt(..),
usage, version,
parseArguments,
ledgerFilePathFromOpts,
beginDateFromOpts,
endDateFromOpts,
parseAccountDescriptionArgs,
)
module Options
where
import System
import System.Console.GetOpt
import System.Directory
import System.Environment (getEnv)
import Data.Maybe (fromMaybe)
import Ledger.Utils
import Ledger.Types

View File

@ -1,3 +1,4 @@
#!/usr/bin/env runhaskell
import Distribution.Simple
main = defaultMain

View File

@ -34,12 +34,11 @@ module Main
where
import System
import qualified Data.Map as Map (lookup)
import Options
import Tests (hunit, quickcheck)
import Ledger.Parse (parseLedgerFile, printParseError)
import Ledger.Utils hiding (test)
import Ledger hiding (rawledger)
import Tests
import Ledger.Parse
import Ledger.Utils
import Ledger
main :: IO ()
@ -99,15 +98,15 @@ parseLedgerAndDo opts args cmd =
-- | get a RawLedger from the file your LEDGER environment variable points to
-- or (WARNING) an empty one if there was a problem.
rawledger :: IO RawLedger
rawledger = do
myrawledger :: IO RawLedger
myrawledger = do
parsed <- ledgerFilePathFromOpts [] >>= parseLedgerFile
return $ either (\_ -> RawLedger [] [] [] "") id parsed
-- | as above, and convert it to a cached Ledger
ledger :: IO Ledger
ledger = do
l <- rawledger
myledger :: IO Ledger
myledger = do
l <- myrawledger
return $ cacheLedger wildcard $ filterLedgerEntries "" "" wildcard wildcard l
-- | get a Ledger from the given file path
@ -118,5 +117,5 @@ rawledgerfromfile f = do
-- | get a named account from your ledger file
accountnamed :: AccountName -> IO Account
accountnamed a = ledger >>= (return . fromMaybe nullacct . Map.lookup a . accounts)
accountnamed a = myledger >>= (return . fromMaybe nullacct . Map.lookup a . accounts)