reduce unnecessary imports

This commit is contained in:
Simon Michael 2008-10-10 02:19:53 +00:00
parent cdc5a23192
commit 73c49ec060
12 changed files with 41 additions and 60 deletions

View File

@ -6,29 +6,31 @@ It generally provides a compatible subset of C++ ledger's functionality.
-} -}
module Ledger ( module Ledger (
module Ledger.Types, module Ledger.Account,
module Ledger.Currency,
module Ledger.Amount,
module Ledger.AccountName, module Ledger.AccountName,
module Ledger.RawTransaction, module Ledger.Amount,
module Ledger.Currency,
module Ledger.Entry, module Ledger.Entry,
module Ledger.Ledger,
module Ledger.Parse,
module Ledger.RawLedger,
module Ledger.RawTransaction,
module Ledger.TimeLog, module Ledger.TimeLog,
module Ledger.Transaction, module Ledger.Transaction,
-- module Ledger.RawLedger, module Ledger.Types,
module Ledger.Account, module Ledger.Utils,
module Ledger.Ledger,
) )
where where
import qualified Data.Map as Map import Ledger.Account
import Ledger.Types
import Ledger.Currency
import Ledger.Amount
import Ledger.AccountName import Ledger.AccountName
import Ledger.RawTransaction import Ledger.Amount
import Ledger.Currency
import Ledger.Entry import Ledger.Entry
import Ledger.Ledger
import Ledger.Parse
import Ledger.RawLedger
import Ledger.RawTransaction
import Ledger.TimeLog import Ledger.TimeLog
import Ledger.Transaction import Ledger.Transaction
import Ledger.RawLedger import Ledger.Types
import Ledger.Account import Ledger.Utils
import Ledger.Ledger

View File

@ -10,11 +10,7 @@ module Ledger.Account
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Ledger.AccountName
import Ledger.Amount import Ledger.Amount
import Ledger.Entry
import Ledger.RawTransaction
import Ledger.Transaction
instance Show Account where instance Show Account where

View File

@ -8,10 +8,10 @@ currently hard-coded.
module Ledger.Currency module Ledger.Currency
where where
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Map ((!))
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
currencies = currencies =
[ [
Currency "$" 1 Currency "$" 1

View File

@ -6,7 +6,6 @@ Parsers for standard ledger and timelog files.
module Ledger.Parse module Ledger.Parse
where where
import qualified Data.Map as Map
import Text.ParserCombinators.Parsec 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
@ -44,7 +43,7 @@ ledgerLanguageDef = LanguageDef {
lexer = P.makeTokenParser ledgerLanguageDef lexer = P.makeTokenParser ledgerLanguageDef
whiteSpace = P.whiteSpace lexer whiteSpace = P.whiteSpace lexer
lexeme = P.lexeme lexer lexeme = P.lexeme lexer
symbol = P.symbol lexer --symbol = P.symbol lexer
natural = P.natural lexer natural = P.natural lexer
parens = P.parens lexer parens = P.parens lexer
semi = P.semi lexer semi = P.semi lexer

View File

@ -7,7 +7,6 @@ the cached 'Ledger'.
module Ledger.RawLedger module Ledger.RawLedger
where where
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

@ -9,7 +9,6 @@ module Ledger.RawTransaction
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Ledger.AccountName
import Ledger.Amount import Ledger.Amount

View File

@ -12,9 +12,6 @@ import Ledger.Utils
import Ledger.Types import Ledger.Types
import Ledger.Currency import Ledger.Currency
import Ledger.Amount import Ledger.Amount
import Ledger.RawTransaction
import Ledger.Entry
import Ledger.RawLedger
instance Show TimeLogEntry where instance Show TimeLogEntry where

View File

@ -9,11 +9,9 @@ module Ledger.Transaction
where where
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Ledger.AccountName
import Ledger.Entry import Ledger.Entry
import Ledger.RawTransaction import Ledger.RawTransaction
import Ledger.Amount import Ledger.Amount
import Ledger.Currency
instance Show Transaction where instance Show Transaction where

View File

@ -5,36 +5,37 @@ Standard always-available imports and utilities.
-} -}
module Ledger.Utils ( module Ledger.Utils (
module Ledger.Utils,
module Char, module Char,
module Data.List, module Data.List,
module Data.Tree, --module Data.Map,
module Data.Ord,
module Data.Maybe, module Data.Maybe,
module Data.Ord,
module Data.Time.Clock,
module Data.Time.Format,
module Data.Tree,
module Debug.Trace,
module Ledger.Utils,
module System.Locale,
module Test.HUnit,
module Test.QuickCheck,
module Text.Printf, module Text.Printf,
module Text.Regex, module Text.Regex,
module Debug.Trace,
module Test.QuickCheck,
module Test.HUnit,
module System.Locale,
module Data.Time.Clock,
module Data.Time.Format
) )
where where
import Char import Char
import Data.List import Data.List
import Data.Tree --import qualified Data.Map as Map
import qualified Data.Map
import Data.Ord
import Data.Maybe import Data.Maybe
import Text.Printf import Data.Ord
import Text.Regex
import Debug.Trace
import Test.QuickCheck hiding (test, Testable)
import Test.HUnit
import System.Locale (defaultTimeLocale)
import Data.Time.Clock (UTCTime, diffUTCTime) import Data.Time.Clock (UTCTime, diffUTCTime)
import Data.Time.Format (ParseTime, parseTime, formatTime) import Data.Time.Format (ParseTime, parseTime, formatTime)
import Data.Tree
import Debug.Trace
import System.Locale (defaultTimeLocale)
import Test.HUnit
import Test.QuickCheck hiding (test, Testable)
import Text.Printf
import Text.Regex
-- regexps -- regexps

View File

@ -3,10 +3,6 @@ where
import System import System
import System.Console.GetOpt import System.Console.GetOpt
import System.Directory import System.Directory
import System.Environment (getEnv)
import Data.Maybe (fromMaybe)
import Ledger.Utils
import Ledger.Types
usagehdr = "Usage: hledger [OPTIONS] "++commands++" [ACCTPATTERNS] [-- DESCPATTERNS]\nOptions:" usagehdr = "Usage: hledger [OPTIONS] "++commands++" [ACCTPATTERNS] [-- DESCPATTERNS]\nOptions:"

View File

@ -2,11 +2,8 @@ module Tests
where where
import qualified Data.Map as Map import qualified Data.Map as Map
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import Options
import Ledger import Ledger
import Ledger.Parse
import Ledger.Utils
-- utils -- utils

View File

@ -32,13 +32,10 @@ This module includes some helpers for working with your ledger in ghci. Examples
module Main module Main
where where
import System
import qualified Data.Map as Map (lookup) import qualified Data.Map as Map (lookup)
import Ledger
import Options import Options
import Tests import Tests
import Ledger.Parse
import Ledger.Utils
import Ledger
main :: IO () main :: IO ()