move Ledger.* to Hledger.Data.*

This commit is contained in:
Simon Michael 2010-05-19 23:08:53 +00:00
parent 518da0c867
commit 7d4593cee9
34 changed files with 184 additions and 183 deletions

View File

@ -7,7 +7,7 @@ A history-aware add command to help with data entry.
module Hledger.Cli.Commands.Add module Hledger.Cli.Commands.Add
where where
import Ledger import Hledger.Data
import Hledger.Cli.Options import Hledger.Cli.Options
import Hledger.Cli.Commands.Register (showRegisterReport) import Hledger.Cli.Commands.Register (showRegisterReport)
#if __GLASGOW_HASKELL__ <= 610 #if __GLASGOW_HASKELL__ <= 610

View File

@ -24,7 +24,7 @@ module Hledger.Cli.Commands.All (
#ifdef CHART #ifdef CHART
module Hledger.Cli.Commands.Chart, module Hledger.Cli.Commands.Chart,
#endif #endif
tests_Commands tests_Hledger_Commands
) )
where where
import Hledger.Cli.Commands.Add import Hledger.Cli.Commands.Add
@ -46,7 +46,7 @@ import Hledger.Cli.Commands.Chart
import Test.HUnit (Test(TestList)) import Test.HUnit (Test(TestList))
tests_Commands = TestList tests_Hledger_Commands = TestList
[ [
-- Hledger.Cli.Commands.Add.tests_Add -- Hledger.Cli.Commands.Add.tests_Add
-- ,Hledger.Cli.Commands.Balance.tests_Balance -- ,Hledger.Cli.Commands.Balance.tests_Balance

View File

@ -97,12 +97,12 @@ balance report:
module Hledger.Cli.Commands.Balance module Hledger.Cli.Commands.Balance
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Amount import Hledger.Data.Amount
import Ledger.AccountName import Hledger.Data.AccountName
import Ledger.Posting import Hledger.Data.Posting
import Ledger.Ledger import Hledger.Data.Ledger
import Hledger.Cli.Options import Hledger.Cli.Options
#if __GLASGOW_HASKELL__ <= 610 #if __GLASGOW_HASKELL__ <= 610
import Prelude hiding ( putStr ) import Prelude hiding ( putStr )

View File

@ -6,11 +6,11 @@ Generate balances pie chart
module Hledger.Cli.Commands.Chart module Hledger.Cli.Commands.Chart
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Amount import Hledger.Data.Amount
import Ledger.Ledger import Hledger.Data.Ledger
import Ledger.Commodity import Hledger.Data.Commodity
import Hledger.Cli.Options import Hledger.Cli.Options
import Control.Monad (liftM3) import Control.Monad (liftM3)

View File

@ -6,17 +6,17 @@ format, and print it on stdout. See the manual for more details.
module Hledger.Cli.Commands.Convert where module Hledger.Cli.Commands.Convert where
import Hledger.Cli.Options (Opt(Debug)) import Hledger.Cli.Options (Opt(Debug))
import Hledger.Version (versionstr) import Hledger.Version (versionstr)
import Ledger.Types (Ledger,AccountName,Transaction(..),Posting(..),PostingType(..)) import Hledger.Data.Types (Ledger,AccountName,Transaction(..),Posting(..),PostingType(..))
import Ledger.Utils (strip, spacenonewline, restofline, parseWithCtx, assertParse, assertParseEqual) import Hledger.Data.Utils (strip, spacenonewline, restofline, parseWithCtx, assertParse, assertParseEqual)
import Ledger.Parse (someamount, emptyCtx, ledgeraccountname) import Hledger.Data.Parse (someamount, emptyCtx, ledgeraccountname)
import Ledger.Amount (nullmixedamt) import Hledger.Data.Amount (nullmixedamt)
import Safe (atDef, maximumDef) import Safe (atDef, maximumDef)
import System.IO (stderr) import System.IO (stderr)
import Text.CSV (parseCSVFromFile, printCSV) import Text.CSV (parseCSVFromFile, printCSV)
import Text.Printf (hPrintf) import Text.Printf (hPrintf)
import Text.RegexPR (matchRegexPR, gsubRegexPR) import Text.RegexPR (matchRegexPR, gsubRegexPR)
import Data.Maybe import Data.Maybe
import Ledger.Dates (firstJust, showDate, parsedate) import Hledger.Data.Dates (firstJust, showDate, parsedate)
import System.Locale (defaultTimeLocale) import System.Locale (defaultTimeLocale)
import Data.Time.Format (parseTime) import Data.Time.Format (parseTime)
import Control.Monad (when, guard, liftM) import Control.Monad (when, guard, liftM)

View File

@ -7,7 +7,7 @@ Print a histogram report.
module Hledger.Cli.Commands.Histogram module Hledger.Cli.Commands.Histogram
where where
import Ledger import Hledger.Data
import Hledger.Cli.Options import Hledger.Cli.Options
#if __GLASGOW_HASKELL__ <= 610 #if __GLASGOW_HASKELL__ <= 610
import Prelude hiding ( putStr ) import Prelude hiding ( putStr )

View File

@ -7,7 +7,7 @@ A ledger-compatible @print@ command.
module Hledger.Cli.Commands.Print module Hledger.Cli.Commands.Print
where where
import Ledger import Hledger.Data
import Hledger.Cli.Options import Hledger.Cli.Options
#if __GLASGOW_HASKELL__ <= 610 #if __GLASGOW_HASKELL__ <= 610
import Prelude hiding ( putStr ) import Prelude hiding ( putStr )

View File

@ -13,7 +13,7 @@ module Hledger.Cli.Commands.Register (
) where ) where
import Safe (headMay, lastMay) import Safe (headMay, lastMay)
import Ledger import Hledger.Data
import Hledger.Cli.Options import Hledger.Cli.Options
#if __GLASGOW_HASKELL__ <= 610 #if __GLASGOW_HASKELL__ <= 610
import Prelude hiding ( putStr ) import Prelude hiding ( putStr )

View File

@ -7,7 +7,7 @@ Print some statistics for the ledger.
module Hledger.Cli.Commands.Stats module Hledger.Cli.Commands.Stats
where where
import Ledger import Hledger.Data
import Hledger.Cli.Options import Hledger.Cli.Options
#if __GLASGOW_HASKELL__ <= 610 #if __GLASGOW_HASKELL__ <= 610
import Prelude hiding ( putStr ) import Prelude hiding ( putStr )

View File

@ -8,7 +8,7 @@ module Hledger.Cli.Commands.UI
where where
import Safe (headDef) import Safe (headDef)
import Graphics.Vty import Graphics.Vty
import Ledger import Hledger.Data
import Hledger.Cli.Options import Hledger.Cli.Options
import Hledger.Cli.Commands.Balance import Hledger.Cli.Commands.Balance
import Hledger.Cli.Commands.Register import Hledger.Cli.Commands.Register

View File

@ -44,7 +44,7 @@ import Hledger.Cli.Commands.Balance
import Hledger.Cli.Commands.Histogram import Hledger.Cli.Commands.Histogram
import Hledger.Cli.Commands.Print import Hledger.Cli.Commands.Print
import Hledger.Cli.Commands.Register import Hledger.Cli.Commands.Register
import Ledger import Hledger.Data
import Hledger.Cli.Options hiding (value) import Hledger.Cli.Options hiding (value)
#ifdef MAKE #ifdef MAKE
import Paths_hledger_make (getDataFileName) import Paths_hledger_make (getDataFileName)

View File

@ -12,7 +12,7 @@ import System.IO.UTF8
#endif #endif
import Hledger.Cli.Commands.All import Hledger.Cli.Commands.All
import Ledger import Hledger.Data
import Hledger.Cli.Options import Hledger.Cli.Options
import Hledger.Tests import Hledger.Tests
import Hledger.Utils (withLedgerDo) import Hledger.Utils (withLedgerDo)

View File

@ -8,10 +8,10 @@ where
import System.Console.GetOpt import System.Console.GetOpt
import System.Environment import System.Environment
import Hledger.Version (timeprogname) import Hledger.Version (timeprogname)
import Ledger.IO (myLedgerPath,myTimelogPath) import Hledger.Data.IO (myLedgerPath,myTimelogPath)
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Dates import Hledger.Data.Dates
#if __GLASGOW_HASKELL__ <= 610 #if __GLASGOW_HASKELL__ <= 610
import Codec.Binary.UTF8.String (decodeString) import Codec.Binary.UTF8.String (decodeString)
#endif #endif

View File

@ -36,7 +36,7 @@ import System.Exit (exitFailure, exitWith, ExitCode(ExitSuccess)) -- base 3 comp
import System.Time (ClockTime(TOD)) import System.Time (ClockTime(TOD))
import Hledger.Cli.Commands.All import Hledger.Cli.Commands.All
import Ledger -- including testing utils in Ledger.Utils import Hledger.Data -- including testing utils in Hledger.Data.Utils
import Hledger.Cli.Options import Hledger.Cli.Options
import Hledger.Utils import Hledger.Utils
@ -59,8 +59,8 @@ runtests opts args = do
-- inconvenient due to import cycles or whatever, we define them here. -- inconvenient due to import cycles or whatever, we define them here.
tests :: Test tests :: Test
tests = TestList [ tests = TestList [
tests_Ledger, tests_Hledger_Data,
tests_Commands, tests_Hledger_Commands,
"account directive" ~: "account directive" ~:
let sameParse str1 str2 = do l1 <- journalFromString str1 let sameParse str1 str2 = do l1 <- journalFromString str1

View File

@ -1,15 +1,15 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-| {-|
Utilities for top-level modules and ghci. See also "Ledger.IO" and Utilities for top-level modules and ghci. See also Hledger.Data.IO and
"Ledger.Utils". Hledger.Data.Utils.
-} -}
module Hledger.Utils module Hledger.Utils
where where
import Control.Monad.Error import Control.Monad.Error
import Ledger import Hledger.Data
import Hledger.Cli.Options (Opt(..),ledgerFilePathFromOpts) -- ,optsToFilterSpec) import Hledger.Cli.Options (Opt(..),ledgerFilePathFromOpts) -- ,optsToFilterSpec)
import System.Directory (doesFileExist) import System.Directory (doesFileExist)
import System.IO (stderr) import System.IO (stderr)

View File

@ -7,7 +7,7 @@ numbering policy.
module Hledger.Version module Hledger.Version
where where
import System.Info (os, arch) import System.Info (os, arch)
import Ledger.Utils import Hledger.Data.Utils
-- version and PATCHLEVEL are set by the makefile -- version and PATCHLEVEL are set by the makefile
version = "0.8.0" version = "0.8.0"

View File

@ -36,7 +36,8 @@ SOURCEFILES:= \
Hledger/Cli/*hs \ Hledger/Cli/*hs \
Hledger/Cli/Commands/*hs \ Hledger/Cli/Commands/*hs \
hledger-lib/*hs \ hledger-lib/*hs \
hledger-lib/Ledger/*hs hledger-lib/Hledger/*hs \
hledger-lib/Hledger/Data/*hs
DOCFILES:=README README2 MANUAL NEWS CONTRIBUTORS SCREENSHOTS DOCFILES:=README README2 MANUAL NEWS CONTRIBUTORS SCREENSHOTS
BINARYFILENAME=`runhaskell ./hledger.hs --binary-filename` BINARYFILENAME=`runhaskell ./hledger.hs --binary-filename`
PATCHLEVEL:=$(shell expr `darcs changes --count --from-tag=\\\\\.` - 1) PATCHLEVEL:=$(shell expr `darcs changes --count --from-tag=\\\\\.` - 1)

View File

@ -0,0 +1,58 @@
{-|
The Ledger library allows parsing and querying of ledger files. It
generally provides a compatible subset of C++ ledger's functionality.
This package re-exports all the Ledger.* modules.
-}
module Hledger.Data (
module Hledger.Data.Account,
module Hledger.Data.AccountName,
module Hledger.Data.Amount,
module Hledger.Data.Commodity,
module Hledger.Data.Dates,
module Hledger.Data.IO,
module Hledger.Data.Transaction,
module Hledger.Data.Ledger,
module Hledger.Data.Parse,
module Hledger.Data.Journal,
module Hledger.Data.Posting,
module Hledger.Data.TimeLog,
module Hledger.Data.Types,
module Hledger.Data.Utils,
tests_Hledger_Data
)
where
import Hledger.Data.Account
import Hledger.Data.AccountName
import Hledger.Data.Amount
import Hledger.Data.Commodity
import Hledger.Data.Dates
import Hledger.Data.IO
import Hledger.Data.Transaction
import Hledger.Data.Ledger
import Hledger.Data.Parse
import Hledger.Data.Journal
import Hledger.Data.Posting
import Hledger.Data.TimeLog
import Hledger.Data.Types
import Hledger.Data.Utils
tests_Hledger_Data = TestList
[
-- Hledger.Data.Account.tests_Account
-- ,Hledger.Data.AccountName.tests_AccountName
Hledger.Data.Amount.tests_Amount
-- ,Hledger.Data.Commodity.tests_Commodity
,Hledger.Data.Dates.tests_Dates
-- ,Hledger.Data.IO.tests_IO
,Hledger.Data.Transaction.tests_Transaction
-- ,Hledger.Data.Hledger.Data.tests_Hledger.Data
,Hledger.Data.Parse.tests_Parse
-- ,Hledger.Data.Journal.tests_Journal
-- ,Hledger.Data.Posting.tests_Posting
-- ,Hledger.Data.TimeLog.tests_TimeLog
-- ,Hledger.Data.Types.tests_Types
-- ,Hledger.Data.Utils.tests_Utils
]

View File

@ -10,11 +10,11 @@ A compound data type for efficiency. An 'Account' stores
-} -}
module Ledger.Account module Hledger.Data.Account
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Amount import Hledger.Data.Amount
instance Show Account where instance Show Account where

View File

@ -6,10 +6,10 @@ From a set of these we derive the account hierarchy.
-} -}
module Ledger.AccountName module Hledger.Data.AccountName
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Data.Map (Map) import Data.Map (Map)
import qualified Data.Map as M import qualified Data.Map as M

View File

@ -38,11 +38,11 @@ price-discarding arithmetic which ignores and discards prices.
-} -}
module Ledger.Amount module Hledger.Data.Amount
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Commodity import Hledger.Data.Commodity
instance Show Amount where show = showAmount instance Show Amount where show = showAmount

View File

@ -6,10 +6,10 @@ display 'Amount's of the commodity - is the symbol on the left or right,
are thousands separated by comma, significant decimal places and so on. are thousands separated by comma, significant decimal places and so on.
-} -}
module Ledger.Commodity module Hledger.Data.Commodity
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
-- convenient amount and commodity constructors, for tests etc. -- convenient amount and commodity constructors, for tests etc.

View File

@ -18,7 +18,7 @@ quarterly, etc.
-} -}
module Ledger.Dates module Hledger.Data.Dates
where where
import Data.Time.Format import Data.Time.Format
@ -27,8 +27,8 @@ import System.Locale (defaultTimeLocale)
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Char import Text.ParserCombinators.Parsec.Char
import Text.ParserCombinators.Parsec.Combinator import Text.ParserCombinators.Parsec.Combinator
import Ledger.Types import Hledger.Data.Types
import Ledger.Utils import Hledger.Data.Utils
showDate :: Day -> String showDate :: Day -> String

View File

@ -3,14 +3,14 @@
Utilities for doing I/O with ledger files. Utilities for doing I/O with ledger files.
-} -}
module Ledger.IO module Hledger.Data.IO
where where
import Control.Monad.Error import Control.Monad.Error
import Ledger.Ledger (cacheLedger', nullledger) import Hledger.Data.Ledger (cacheLedger', nullledger)
import Ledger.Parse (parseLedger) import Hledger.Data.Parse (parseLedger)
import Ledger.Types (FilterSpec(..),WhichDate(..),Journal(..),Ledger(..)) import Hledger.Data.Types (FilterSpec(..),WhichDate(..),Journal(..),Ledger(..))
import Ledger.Utils (getCurrentLocalTime) import Hledger.Data.Utils (getCurrentLocalTime)
import Ledger.Dates (nulldatespan) import Hledger.Data.Dates (nulldatespan)
import System.Directory (getHomeDirectory) import System.Directory (getHomeDirectory)
import System.Environment (getEnv) import System.Environment (getEnv)
#if __GLASGOW_HASKELL__ <= 610 #if __GLASGOW_HASKELL__ <= 610

View File

@ -6,18 +6,18 @@ to form a 'Ledger'.
-} -}
module Ledger.Journal module Hledger.Data.Journal
where where
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Map (findWithDefault, (!)) import Data.Map (findWithDefault, (!))
import System.Time (ClockTime(TOD)) import System.Time (ClockTime(TOD))
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.AccountName import Hledger.Data.AccountName
import Ledger.Amount import Hledger.Data.Amount
import Ledger.Transaction (ledgerTransactionWithDate) import Hledger.Data.Transaction (ledgerTransactionWithDate)
import Ledger.Posting import Hledger.Data.Posting
import Ledger.TimeLog import Hledger.Data.TimeLog
instance Show Journal where instance Show Journal where

View File

@ -17,7 +17,7 @@ This is the main object you'll deal with as a user of the Ledger
library. The most useful functions also have shorter, lower-case library. The most useful functions also have shorter, lower-case
aliases for easier interaction. Here's an example: aliases for easier interaction. Here's an example:
> > import Ledger > > import Hledger.Data
> > l <- readLedger "sample.ledger" > > l <- readLedger "sample.ledger"
> > accountnames l > > accountnames l
> ["assets","assets:bank","assets:bank:checking","assets:bank:saving",... > ["assets","assets:bank","assets:bank:checking","assets:bank:saving",...
@ -51,16 +51,16 @@ aliases for easier interaction. Here's an example:
-} -}
module Ledger.Ledger module Hledger.Data.Ledger
where where
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Map (findWithDefault, fromList) import Data.Map (findWithDefault, fromList)
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Account (nullacct) import Hledger.Data.Account (nullacct)
import Ledger.AccountName import Hledger.Data.AccountName
import Ledger.Journal import Hledger.Data.Journal
import Ledger.Posting import Hledger.Data.Posting
instance Show Ledger where instance Show Ledger where

View File

@ -140,7 +140,7 @@ o 2007/03/10 17:26:02
-} -}
module Ledger.Parse module Hledger.Data.Parse
where where
import Control.Monad.Error (ErrorT(..), MonadIO, liftIO, throwError, catchError) import Control.Monad.Error (ErrorT(..), MonadIO, liftIO, throwError, catchError)
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
@ -151,15 +151,15 @@ import System.Directory
import Prelude hiding (readFile, putStr, putStrLn, print, getContents) import Prelude hiding (readFile, putStr, putStrLn, print, getContents)
import System.IO.UTF8 import System.IO.UTF8
#endif #endif
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Dates import Hledger.Data.Dates
import Ledger.AccountName (accountNameFromComponents,accountNameComponents) import Hledger.Data.AccountName (accountNameFromComponents,accountNameComponents)
import Ledger.Amount import Hledger.Data.Amount
import Ledger.Transaction import Hledger.Data.Transaction
import Ledger.Posting import Hledger.Data.Posting
import Ledger.Journal import Hledger.Data.Journal
import Ledger.Commodity (dollars,dollar,unknown) import Hledger.Data.Commodity (dollars,dollar,unknown)
import System.FilePath(takeDirectory,combine) import System.FilePath(takeDirectory,combine)

View File

@ -7,13 +7,13 @@ we can get a date or description for a posting (from the transaction).
-} -}
module Ledger.Posting module Hledger.Data.Posting
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Amount import Hledger.Data.Amount
import Ledger.AccountName import Hledger.Data.AccountName
import Ledger.Dates (nulldate) import Hledger.Data.Dates (nulldate)
instance Show Posting where show = showPosting instance Show Posting where show = showPosting

View File

@ -6,13 +6,13 @@ converted to 'Transactions' and queried like a ledger.
-} -}
module Ledger.TimeLog module Hledger.Data.TimeLog
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Dates import Hledger.Data.Dates
import Ledger.Commodity import Hledger.Data.Commodity
import Ledger.Transaction import Hledger.Data.Transaction
instance Show TimeLogEntry where instance Show TimeLogEntry where
show t = printf "%s %s %s" (show $ tlcode t) (show $ tldatetime t) (tlcomment t) show t = printf "%s %s %s" (show $ tlcode t) (show $ tldatetime t) (tlcomment t)

View File

@ -5,14 +5,14 @@ normally contains two or more balanced 'Posting's.
-} -}
module Ledger.Transaction module Hledger.Data.Transaction
where where
import Ledger.Utils import Hledger.Data.Utils
import Ledger.Types import Hledger.Data.Types
import Ledger.Dates import Hledger.Data.Dates
import Ledger.Posting import Hledger.Data.Posting
import Ledger.Amount import Hledger.Data.Amount
import Ledger.Commodity (dollars, dollar, unknown) import Hledger.Data.Commodity (dollars, dollar, unknown)
instance Show Transaction where show = showTransactionUnelided instance Show Transaction where show = showTransactionUnelided

View File

@ -27,9 +27,9 @@ Terminology has been in flux:
-} -}
module Ledger.Types module Hledger.Data.Types
where where
import Ledger.Utils import Hledger.Data.Utils
import qualified Data.Map as Map import qualified Data.Map as Map
import System.Time (ClockTime) import System.Time (ClockTime)
import Data.Typeable (Typeable) import Data.Typeable (Typeable)

View File

@ -6,7 +6,7 @@ needed low in the module hierarchy. This is the bottom of the dependency graph.
-} -}
module Ledger.Utils ( module Hledger.Data.Utils (
module Data.Char, module Data.Char,
module Control.Monad, module Control.Monad,
module Data.List, module Data.List,
@ -18,7 +18,7 @@ module Data.Time.Clock,
module Data.Time.Calendar, module Data.Time.Calendar,
module Data.Time.LocalTime, module Data.Time.LocalTime,
module Debug.Trace, module Debug.Trace,
module Ledger.Utils, module Hledger.Data.Utils,
module Text.Printf, module Text.Printf,
module Text.RegexPR, module Text.RegexPR,
module Test.HUnit, module Test.HUnit,

View File

@ -1,58 +0,0 @@
{-|
The Ledger library allows parsing and querying of ledger files. It
generally provides a compatible subset of C++ ledger's functionality.
This package re-exports all the Ledger.* modules.
-}
module Ledger (
module Ledger.Account,
module Ledger.AccountName,
module Ledger.Amount,
module Ledger.Commodity,
module Ledger.Dates,
module Ledger.IO,
module Ledger.Transaction,
module Ledger.Ledger,
module Ledger.Parse,
module Ledger.Journal,
module Ledger.Posting,
module Ledger.TimeLog,
module Ledger.Types,
module Ledger.Utils,
tests_Ledger
)
where
import Ledger.Account
import Ledger.AccountName
import Ledger.Amount
import Ledger.Commodity
import Ledger.Dates
import Ledger.IO
import Ledger.Transaction
import Ledger.Ledger
import Ledger.Parse
import Ledger.Journal
import Ledger.Posting
import Ledger.TimeLog
import Ledger.Types
import Ledger.Utils
tests_Ledger = TestList
[
-- Ledger.Account.tests_Account
-- ,Ledger.AccountName.tests_AccountName
Ledger.Amount.tests_Amount
-- ,Ledger.Commodity.tests_Commodity
,Ledger.Dates.tests_Dates
-- ,Ledger.IO.tests_IO
,Ledger.Transaction.tests_Transaction
-- ,Ledger.Ledger.tests_Ledger
,Ledger.Parse.tests_Parse
-- ,Ledger.Journal.tests_Journal
-- ,Ledger.Posting.tests_Posting
-- ,Ledger.TimeLog.tests_TimeLog
-- ,Ledger.Types.tests_Types
-- ,Ledger.Utils.tests_Utils
]

View File

@ -26,21 +26,21 @@ build-type: Simple
library library
exposed-modules: exposed-modules:
Ledger Hledger.Data
Ledger.Account Hledger.Data.Account
Ledger.AccountName Hledger.Data.AccountName
Ledger.Amount Hledger.Data.Amount
Ledger.Commodity Hledger.Data.Commodity
Ledger.Dates Hledger.Data.Dates
Ledger.IO Hledger.Data.IO
Ledger.Transaction Hledger.Data.Transaction
Ledger.Journal Hledger.Data.Journal
Ledger.Ledger Hledger.Data.Ledger
Ledger.Posting Hledger.Data.Posting
Ledger.Parse Hledger.Data.Parse
Ledger.TimeLog Hledger.Data.TimeLog
Ledger.Types Hledger.Data.Types
Ledger.Utils Hledger.Data.Utils
Build-Depends: Build-Depends:
base >= 3 && < 5 base >= 3 && < 5
,containers ,containers