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.Types,
module Ledger.Currency,
module Ledger.Amount,
module Ledger.Account,
module Ledger.AccountName,
module Ledger.RawTransaction,
module Ledger.Amount,
module Ledger.Currency,
module Ledger.Entry,
module Ledger.Ledger,
module Ledger.Parse,
module Ledger.RawLedger,
module Ledger.RawTransaction,
module Ledger.TimeLog,
module Ledger.Transaction,
-- module Ledger.RawLedger,
module Ledger.Account,
module Ledger.Ledger,
module Ledger.Types,
module Ledger.Utils,
)
where
import qualified Data.Map as Map
import Ledger.Types
import Ledger.Currency
import Ledger.Amount
import Ledger.Account
import Ledger.AccountName
import Ledger.RawTransaction
import Ledger.Amount
import Ledger.Currency
import Ledger.Entry
import Ledger.Ledger
import Ledger.Parse
import Ledger.RawLedger
import Ledger.RawTransaction
import Ledger.TimeLog
import Ledger.Transaction
import Ledger.RawLedger
import Ledger.Account
import Ledger.Ledger
import Ledger.Types
import Ledger.Utils

View File

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

View File

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

View File

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

View File

@ -7,7 +7,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

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

View File

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

View File

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

View File

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

View File

@ -3,10 +3,6 @@ where
import System
import System.Console.GetOpt
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:"

View File

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

View File

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