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 where
import qualified Data.Map as Map import qualified Data.Map as Map
import Ledger.Types import Ledger.Types
import Ledger.Currency import Ledger.Currency
import Ledger.Amount import Ledger.Amount

View File

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

View File

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

View File

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

View File

@ -8,7 +8,6 @@ the cached 'Ledger'.
module Ledger.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 Ledger.AccountName import Ledger.AccountName

View File

@ -8,7 +8,6 @@ containing zero or more 'TimeLogEntry's. It can be converted to a
module Ledger.TimeLog module Ledger.TimeLog
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Ledger.Currency import Ledger.Currency
@ -17,6 +16,7 @@ import Ledger.RawTransaction
import Ledger.Entry import Ledger.Entry
import Ledger.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

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

View File

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

View File

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

View File

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

View File

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