imports, api cleanup
This commit is contained in:
parent
218e1c2f39
commit
5084280879
@ -23,7 +23,7 @@ import Hledger.Cli.Utils (withJournalDo)
|
||||
import Hledger.Cli.Version (progversionstr, binaryfilename)
|
||||
import Hledger.Data
|
||||
import Prelude hiding (putStr, putStrLn)
|
||||
import Hledger.Data.UTF8 (putStr, putStrLn)
|
||||
import Hledger.Utils.UTF8 (putStr, putStrLn)
|
||||
|
||||
|
||||
progname_chart = progname_cli ++ "-chart"
|
||||
|
||||
@ -20,10 +20,11 @@ module Hledger.Data (
|
||||
module Hledger.Data.TimeLog,
|
||||
module Hledger.Data.Transaction,
|
||||
module Hledger.Data.Types,
|
||||
module Hledger.Data.Utils,
|
||||
tests_Hledger_Data
|
||||
)
|
||||
where
|
||||
import Test.HUnit
|
||||
|
||||
import Hledger.Data.Account
|
||||
import Hledger.Data.AccountName
|
||||
import Hledger.Data.Amount
|
||||
@ -36,7 +37,6 @@ import Hledger.Data.Posting
|
||||
import Hledger.Data.TimeLog
|
||||
import Hledger.Data.Transaction
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Utils
|
||||
|
||||
tests_Hledger_Data = TestList
|
||||
[
|
||||
@ -51,5 +51,4 @@ tests_Hledger_Data = TestList
|
||||
,tests_Hledger_Data_TimeLog
|
||||
,tests_Hledger_Data_Transaction
|
||||
-- ,tests_Hledger_Data_Types
|
||||
-- ,tests_Hledger_Data_Utils
|
||||
]
|
||||
|
||||
@ -12,9 +12,11 @@ An 'Account' stores
|
||||
|
||||
module Hledger.Data.Account
|
||||
where
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Data.Types
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Data.Amount
|
||||
import Hledger.Data.Types
|
||||
|
||||
|
||||
instance Show Account where
|
||||
|
||||
@ -9,11 +9,15 @@ hierarchy.
|
||||
|
||||
module Hledger.Data.AccountName
|
||||
where
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Data.Types
|
||||
import Data.List
|
||||
import Data.Map (Map)
|
||||
import Data.Tree
|
||||
import Test.HUnit
|
||||
import qualified Data.Map as M
|
||||
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
|
||||
-- change to use a different separator for nested accounts
|
||||
|
||||
@ -70,15 +70,19 @@ module Hledger.Data.Amount (
|
||||
showMixedAmountWithPrecision,
|
||||
sumMixedAmountsPreservingHighestPrecision,
|
||||
tests_Hledger_Data_Amount
|
||||
-- Hledger.Data.Amount.tests_Hledger_Data_Amount
|
||||
)
|
||||
where
|
||||
import qualified Data.Map as Map
|
||||
import Data.Char (isDigit)
|
||||
import Data.List
|
||||
import Data.Map (findWithDefault)
|
||||
import Data.Ord
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Commodity
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
instance Show Amount where show = showAmount
|
||||
|
||||
@ -8,10 +8,14 @@ are thousands separated by comma, significant decimal places and so on.
|
||||
-}
|
||||
module Hledger.Data.Commodity
|
||||
where
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Data.Types
|
||||
import qualified Data.Map as Map
|
||||
import Data.List
|
||||
import Data.Map ((!))
|
||||
import Data.Maybe
|
||||
import Test.HUnit
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
nonsimplecommoditychars = "0123456789-.@;\n \""
|
||||
|
||||
@ -23,13 +23,22 @@ quarterly, etc.
|
||||
module Hledger.Data.Dates
|
||||
where
|
||||
|
||||
import Control.Monad
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Time.Format
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.Calendar.OrdinalDate
|
||||
import Data.Time.Clock
|
||||
import Data.Time.LocalTime
|
||||
import Safe (readMay)
|
||||
import System.Locale (defaultTimeLocale)
|
||||
import Test.HUnit
|
||||
import Text.ParserCombinators.Parsec
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
showDate :: Day -> String
|
||||
|
||||
@ -8,11 +8,19 @@ data object.
|
||||
|
||||
module Hledger.Data.Journal
|
||||
where
|
||||
import qualified Data.Map as Map
|
||||
import Data.List
|
||||
import Data.Map (findWithDefault, (!))
|
||||
import Data.Ord
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.LocalTime
|
||||
import Data.Tree
|
||||
import Safe (headDef)
|
||||
import System.Time (ClockTime(TOD))
|
||||
import Hledger.Data.Utils
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Hledger.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.AccountName
|
||||
import Hledger.Data.Amount
|
||||
@ -50,6 +58,7 @@ nulljournal = Journal { jmodifiertxns = []
|
||||
nullctx :: JournalContext
|
||||
nullctx = Ctx { ctxYear = Nothing, ctxCommodity = Nothing, ctxAccount = [] }
|
||||
|
||||
nullfilterspec :: FilterSpec
|
||||
nullfilterspec = FilterSpec {
|
||||
datespan=nulldatespan
|
||||
,cleared=Nothing
|
||||
|
||||
@ -10,7 +10,11 @@ balances, and postings in each account.
|
||||
module Hledger.Data.Ledger
|
||||
where
|
||||
import Data.Map (Map, findWithDefault, fromList)
|
||||
import Hledger.Data.Utils
|
||||
import Data.Tree
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Account (nullacct)
|
||||
import Hledger.Data.AccountName
|
||||
|
||||
@ -10,7 +10,13 @@ Strictly speaking, \"entry\" is probably a better name for these.
|
||||
|
||||
module Hledger.Data.Posting
|
||||
where
|
||||
import Hledger.Data.Utils
|
||||
import Data.List
|
||||
import Data.Ord
|
||||
import Data.Time.Calendar
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Amount
|
||||
import Hledger.Data.AccountName
|
||||
|
||||
@ -8,9 +8,16 @@ converted to 'Transactions' and queried like a ledger.
|
||||
|
||||
module Hledger.Data.TimeLog
|
||||
where
|
||||
import Data.Maybe
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.Clock
|
||||
import Data.Time.Format
|
||||
import Data.Time.LocalTime
|
||||
import System.Locale (defaultTimeLocale)
|
||||
import Hledger.Data.Utils
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Dates
|
||||
import Hledger.Data.Commodity
|
||||
|
||||
@ -8,9 +8,13 @@ plus a date and optional metadata like description and cleared status.
|
||||
|
||||
module Hledger.Data.Transaction
|
||||
where
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Dates
|
||||
import Hledger.Data.Posting
|
||||
|
||||
@ -33,12 +33,13 @@ Evolution of transaction\/entry\/posting terminology:
|
||||
module Hledger.Data.Types
|
||||
where
|
||||
import Control.Monad.Error (ErrorT)
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.LocalTime
|
||||
import Data.Tree
|
||||
import Data.Typeable (Typeable)
|
||||
import qualified Data.Map as Map
|
||||
import System.Time (ClockTime)
|
||||
|
||||
import Hledger.Data.Utils
|
||||
|
||||
|
||||
type SmartDate = (String,String,String)
|
||||
|
||||
|
||||
@ -18,20 +18,23 @@ module Hledger.Read (
|
||||
where
|
||||
import Control.Monad.Error
|
||||
import Data.Either (partitionEithers)
|
||||
import Data.List
|
||||
import Safe (headDef)
|
||||
import System.Directory (doesFileExist, getHomeDirectory)
|
||||
import System.Environment (getEnv)
|
||||
import System.FilePath ((</>))
|
||||
import System.IO (IOMode(..), withFile, stderr)
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Data.Dates (getCurrentDay)
|
||||
import Hledger.Data.Types (Journal(..), Reader(..))
|
||||
import Hledger.Data.Journal (nullctx)
|
||||
import Hledger.Data.Utils
|
||||
import Prelude hiding (getContents)
|
||||
import Hledger.Data.UTF8 (getContents, hGetContents)
|
||||
import Hledger.Read.JournalReader as JournalReader
|
||||
import Hledger.Read.TimelogReader as TimelogReader
|
||||
import Hledger.Utils
|
||||
import Prelude hiding (getContents)
|
||||
import Hledger.Utils.UTF8 (getContents, hGetContents)
|
||||
|
||||
|
||||
journalenvvar = "LEDGER_FILE"
|
||||
|
||||
@ -117,15 +117,24 @@ module Hledger.Read.JournalReader (
|
||||
tests_Hledger_Read_JournalReader
|
||||
)
|
||||
where
|
||||
import Control.Monad.Error (ErrorT(..), throwError, catchError)
|
||||
import Control.Monad
|
||||
import Control.Monad.Error
|
||||
import Data.Char (isNumber)
|
||||
import Data.List
|
||||
import Data.List.Split (wordsBy)
|
||||
import Data.Maybe
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.LocalTime
|
||||
import Safe (headDef)
|
||||
import Test.HUnit
|
||||
import Text.ParserCombinators.Parsec hiding (parse)
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Data
|
||||
import Prelude hiding (readFile)
|
||||
import Hledger.Data.UTF8 (readFile)
|
||||
import Hledger.Read.Utils
|
||||
import Hledger.Utils
|
||||
import Prelude hiding (readFile)
|
||||
import Hledger.Utils.UTF8 (readFile)
|
||||
|
||||
|
||||
-- let's get to it
|
||||
|
||||
@ -47,12 +47,16 @@ module Hledger.Read.TimelogReader (
|
||||
tests_Hledger_Read_TimelogReader
|
||||
)
|
||||
where
|
||||
import Control.Monad.Error (ErrorT(..))
|
||||
import Control.Monad
|
||||
import Control.Monad.Error
|
||||
import Test.HUnit
|
||||
import Text.ParserCombinators.Parsec hiding (parse)
|
||||
|
||||
import Hledger.Data
|
||||
import Hledger.Read.Utils
|
||||
import Hledger.Read.JournalReader (ledgerExclamationDirective, ledgerHistoricalPrice,
|
||||
ledgerDefaultYear, emptyLine, ledgerdatetime)
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
reader :: Reader
|
||||
|
||||
@ -6,13 +6,14 @@ module Hledger.Read.Utils
|
||||
where
|
||||
|
||||
import Control.Monad.Error
|
||||
import Data.List
|
||||
import System.Directory (getHomeDirectory)
|
||||
import System.FilePath(takeDirectory,combine)
|
||||
import System.Time (getClockTime)
|
||||
import Text.ParserCombinators.Parsec
|
||||
|
||||
import Hledger.Data.Types (Journal, JournalContext(..), Commodity, JournalUpdate)
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Utils
|
||||
import Hledger.Data.Dates (getCurrentYear)
|
||||
import Hledger.Data.Journal (nullctx, nulljournal, journalFinalise)
|
||||
|
||||
|
||||
@ -6,46 +6,40 @@ in the module hierarchy. This is the bottom of hledger's module graph.
|
||||
|
||||
-}
|
||||
|
||||
module Hledger.Data.Utils (
|
||||
module Data.Char,
|
||||
module Control.Monad,
|
||||
module Data.List,
|
||||
--module Data.Map,
|
||||
module Data.Maybe,
|
||||
module Data.Ord,
|
||||
module Data.Tree,
|
||||
module Data.Time.Clock,
|
||||
module Data.Time.Calendar,
|
||||
module Data.Time.LocalTime,
|
||||
module Debug.Trace,
|
||||
module Hledger.Data.Utils,
|
||||
-- module Hledger.Data.UTF8,
|
||||
module Text.Printf,
|
||||
module Text.RegexPR,
|
||||
module Test.HUnit,
|
||||
)
|
||||
module Hledger.Utils (---- provide these frequently used modules - or not, for clearer api:
|
||||
-- module Control.Monad,
|
||||
-- module Data.List,
|
||||
-- module Data.Maybe,
|
||||
-- module Data.Time.Calendar,
|
||||
-- module Data.Time.Clock,
|
||||
-- module Data.Time.LocalTime,
|
||||
-- module Data.Tree,
|
||||
-- module Debug.Trace,
|
||||
-- module Text.RegexPR,
|
||||
-- module Test.HUnit,
|
||||
-- module Text.Printf,
|
||||
---- all of this one:
|
||||
module Hledger.Utils
|
||||
---- and this for i18n - needs to be done in each module I think:
|
||||
-- module Hledger.Utils.UTF8
|
||||
)
|
||||
where
|
||||
import Data.Char
|
||||
import Codec.Binary.UTF8.String as UTF8 (decodeString, encodeString, isUTF8Encoded)
|
||||
import Control.Monad
|
||||
import Data.Char
|
||||
import Data.List
|
||||
--import qualified Data.Map as Map
|
||||
import Data.Maybe
|
||||
import Data.Ord
|
||||
import Data.Tree
|
||||
import Data.Time.Clock
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.LocalTime
|
||||
import Data.Tree
|
||||
import Debug.Trace
|
||||
-- needs to be done in each module I think
|
||||
-- import Prelude hiding (readFile,writeFile,getContents,putStr,putStrLn)
|
||||
-- import Hledger.Data.UTF8
|
||||
import System.Info (os)
|
||||
import Test.HUnit
|
||||
import Text.ParserCombinators.Parsec
|
||||
import Text.Printf
|
||||
import Text.RegexPR
|
||||
import Text.ParserCombinators.Parsec
|
||||
import System.Info (os)
|
||||
|
||||
-- import qualified Data.Map as Map
|
||||
--
|
||||
-- import Prelude hiding (readFile,writeFile,getContents,putStr,putStrLn)
|
||||
-- import Hledger.Utils.UTF8
|
||||
|
||||
-- strings
|
||||
|
||||
@ -219,7 +213,6 @@ containsRegex r s = case matchRegexPR ("(?i)"++r) s of
|
||||
Just _ -> True
|
||||
_ -> False
|
||||
|
||||
|
||||
-- lists
|
||||
|
||||
splitAtElement :: Eq a => a -> [a] -> [[a]]
|
||||
@ -375,7 +368,6 @@ assertParseEqual parse expected = either (assertFailure.show) (`is` expected) pa
|
||||
printParseError :: (Show a) => a -> IO ()
|
||||
printParseError e = do putStr "parse error at "; print e
|
||||
|
||||
|
||||
-- misc
|
||||
|
||||
isLeft :: Either a b -> Bool
|
||||
@ -385,17 +377,6 @@ isLeft _ = False
|
||||
isRight :: Either a b -> Bool
|
||||
isRight = not . isLeft
|
||||
|
||||
-- -- | Expand ~ in a file path (does not handle ~name).
|
||||
-- tildeExpand :: FilePath -> IO FilePath
|
||||
-- tildeExpand ('~':[]) = getHomeDirectory
|
||||
-- tildeExpand ('~':'/':xs) = getHomeDirectory >>= return . (++ ('/':xs))
|
||||
-- --handle ~name, requires -fvia-C or ghc 6.8:
|
||||
-- --import System.Posix.User
|
||||
-- -- tildeExpand ('~':xs) = do let (user, path) = span (/= '/') xs
|
||||
-- -- pw <- getUserEntryForName user
|
||||
-- -- return (homeDirectory pw ++ path)
|
||||
-- tildeExpand xs = return xs
|
||||
|
||||
-- | Apply a function the specified number of times. Possibly uses O(n) stack ?
|
||||
applyN :: Int -> (a -> a) -> a -> a
|
||||
applyN n f = (!! n) . iterate f
|
||||
@ -1,5 +1,9 @@
|
||||
{-
|
||||
From pandoc, slightly extended.
|
||||
From pandoc, slightly extended. Example usage:
|
||||
|
||||
import Prelude hiding (readFile,writeFile,getContents,putStr,putStrLn)
|
||||
import Hledger.Utils.UTF8 (readFile,writeFile,getContents,putStr,putStrLn)
|
||||
|
||||
|
||||
----------------------------------------------------------------------
|
||||
Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu>
|
||||
@ -30,7 +34,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
|
||||
UTF-8 aware string IO functions that will work with GHC 6.10 or 6.12.
|
||||
-}
|
||||
module Hledger.Data.UTF8 ( readFile
|
||||
module Hledger.Utils.UTF8 ( readFile
|
||||
, writeFile
|
||||
, appendFile
|
||||
, getContents
|
||||
@ -29,6 +29,7 @@ library
|
||||
-- should set patchlevel here as in Makefile
|
||||
cpp-options: -DPATCHLEVEL=0
|
||||
exposed-modules:
|
||||
Hledger
|
||||
Hledger.Data
|
||||
Hledger.Data.Account
|
||||
Hledger.Data.AccountName
|
||||
@ -41,12 +42,12 @@ library
|
||||
Hledger.Data.Posting
|
||||
Hledger.Data.TimeLog
|
||||
Hledger.Data.Types
|
||||
Hledger.Data.Utils
|
||||
Hledger.Data.UTF8
|
||||
Hledger.Read
|
||||
Hledger.Read.Utils
|
||||
Hledger.Read.JournalReader
|
||||
Hledger.Read.TimelogReader
|
||||
Hledger.Read.Utils
|
||||
Hledger.Utils
|
||||
Hledger.Utils.UTF8
|
||||
Build-Depends:
|
||||
base >= 3 && < 5
|
||||
,bytestring
|
||||
|
||||
@ -19,7 +19,7 @@ import Hledger.Cli.Utils (withJournalDo)
|
||||
import Hledger.Cli.Version (progversionstr, binaryfilename)
|
||||
import Hledger.Data
|
||||
import Prelude hiding (putStr, putStrLn)
|
||||
import Hledger.Data.UTF8 (putStr, putStrLn)
|
||||
import Hledger.Utils.UTF8 (putStr, putStrLn)
|
||||
|
||||
|
||||
progname_vty = progname_cli ++ "-vty"
|
||||
|
||||
@ -24,13 +24,7 @@ import Text.RegexPR
|
||||
import Yesod.Form
|
||||
import Yesod.Json
|
||||
|
||||
import Hledger.Cli.Add
|
||||
import Hledger.Cli.Balance
|
||||
import Hledger.Cli.Print
|
||||
import Hledger.Cli.Register
|
||||
import Hledger.Cli.Options hiding (value)
|
||||
import Hledger.Cli.Utils
|
||||
import Hledger.Cli.Version (version)
|
||||
import Hledger.Cli
|
||||
import Hledger.Cli.Version -- XXX
|
||||
import Hledger.Data hiding (today)
|
||||
import Hledger.Read (journalFromPathAndString)
|
||||
|
||||
@ -8,7 +8,6 @@ Released under GPL version 3 or later.
|
||||
module Main
|
||||
where
|
||||
|
||||
import Prelude hiding (putStr, putStrLn)
|
||||
-- import Control.Concurrent (forkIO, threadDelay)
|
||||
import Data.Maybe
|
||||
import Data.Text(pack)
|
||||
@ -27,7 +26,8 @@ import Hledger.Cli.Options
|
||||
import Hledger.Cli.Utils (withJournalDo) --, openBrowserOn)
|
||||
import Hledger.Cli.Version (progversionstr, binaryfilename)
|
||||
import Hledger.Data
|
||||
import Hledger.Data.UTF8 (putStr, putStrLn)
|
||||
import Prelude hiding (putStr, putStrLn)
|
||||
import Hledger.Utils.UTF8 (putStr, putStrLn)
|
||||
|
||||
import App
|
||||
import AppRun (withApp)
|
||||
|
||||
@ -16,6 +16,13 @@ module Hledger.Cli (
|
||||
tests_Hledger_Cli
|
||||
)
|
||||
where
|
||||
import Control.Monad
|
||||
import qualified Data.Map as Map
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.LocalTime
|
||||
import System.Time (ClockTime(TOD))
|
||||
import Test.HUnit
|
||||
|
||||
import Hledger.Cli.Add
|
||||
import Hledger.Cli.Balance
|
||||
import Hledger.Cli.Convert
|
||||
@ -25,14 +32,10 @@ import Hledger.Cli.Register
|
||||
import Hledger.Cli.Stats
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Cli.Utils
|
||||
|
||||
|
||||
import qualified Data.Map as Map
|
||||
import System.Time (ClockTime(TOD))
|
||||
|
||||
import Hledger.Data -- including testing utils in Hledger.Data.Utils
|
||||
import Hledger.Read
|
||||
import Hledger.Read.JournalReader (someamount)
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
-- | hledger and hledger-lib's unit tests aggregated from all modules
|
||||
|
||||
@ -11,25 +11,32 @@ informational messages are mostly written to stderr rather than stdout.
|
||||
|
||||
module Hledger.Cli.Add
|
||||
where
|
||||
import Hledger.Data
|
||||
import Hledger.Read.JournalReader (someamount)
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Cli.Register (registerReport, registerReportAsText)
|
||||
import Prelude hiding (putStr, putStrLn, appendFile)
|
||||
import Hledger.Data.UTF8 (putStr, putStrLn, appendFile)
|
||||
|
||||
import Control.Exception (throw)
|
||||
import Control.Monad
|
||||
import Control.Monad.Trans (liftIO)
|
||||
import Data.Char (toUpper)
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Time.Calendar
|
||||
import Safe (headMay)
|
||||
import System.Console.Haskeline (InputT, runInputT, defaultSettings, setComplete, getInputLine)
|
||||
import System.Console.Haskeline.Completion
|
||||
import System.IO ( stderr, hPutStrLn, hPutStr )
|
||||
import System.IO.Error
|
||||
import Text.ParserCombinators.Parsec
|
||||
import Hledger.Cli.Utils (readJournalWithOpts)
|
||||
import Text.Printf
|
||||
import qualified Data.Foldable as Foldable (find)
|
||||
import System.Console.Haskeline (
|
||||
InputT, runInputT, defaultSettings, setComplete, getInputLine)
|
||||
import Control.Monad.Trans (liftIO)
|
||||
import System.Console.Haskeline.Completion
|
||||
import qualified Data.Set as Set
|
||||
import Safe (headMay)
|
||||
import Control.Exception (throw)
|
||||
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Cli.Register (registerReport, registerReportAsText)
|
||||
import Hledger.Cli.Utils (readJournalWithOpts)
|
||||
import Hledger.Data
|
||||
import Hledger.Read.JournalReader (someamount)
|
||||
import Hledger.Utils
|
||||
import Prelude hiding (putStr, putStrLn, appendFile)
|
||||
import Hledger.Utils.UTF8 (putStr, putStrLn, appendFile)
|
||||
|
||||
|
||||
{- | Information used as the basis for suggested account names, amounts,
|
||||
etc in add prompt
|
||||
@ -200,6 +207,9 @@ appendToJournalFile f s =
|
||||
then putStr $ sep ++ s
|
||||
else appendFile f $ sep++s
|
||||
where
|
||||
-- appendFile means we don't need file locking to be
|
||||
-- multi-user-safe, but also that we can't figure out the minimal
|
||||
-- number of newlines needed as separator
|
||||
sep = "\n\n"
|
||||
-- sep | null $ strip t = ""
|
||||
-- | otherwise = replicate (2 - min 2 (length lastnls)) '\n'
|
||||
|
||||
@ -104,15 +104,16 @@ module Hledger.Cli.Balance (
|
||||
,tests_Hledger_Cli_Balance
|
||||
-- ,tests_Balance
|
||||
) where
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Amount
|
||||
import Hledger.Data.AccountName
|
||||
import Hledger.Data.Posting
|
||||
import Hledger.Data.Ledger
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Tree
|
||||
import Test.HUnit
|
||||
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Data
|
||||
import Hledger.Utils
|
||||
import Prelude hiding (putStr)
|
||||
import Hledger.Data.UTF8 (putStr)
|
||||
import Hledger.Utils.UTF8 (putStr)
|
||||
|
||||
|
||||
-- | A balance report is a chart of accounts with balances, and their grand total.
|
||||
|
||||
@ -4,30 +4,30 @@ format, and print it on stdout. See the manual for more details.
|
||||
-}
|
||||
|
||||
module Hledger.Cli.Convert where
|
||||
import Hledger.Cli.Options (Opt(Debug), progname_cli)
|
||||
import Hledger.Cli.Version (progversionstr)
|
||||
import Hledger.Data.Types (Journal,AccountName,Transaction(..),Posting(..),PostingType(..))
|
||||
import Hledger.Data.Utils (strip, spacenonewline, restofline, parseWithCtx, assertParse, assertParseEqual, error')
|
||||
import Hledger.Read.JournalReader (someamount,ledgeraccountname)
|
||||
import Hledger.Data.Journal (nullctx)
|
||||
import Hledger.Data.Amount (nullmixedamt, costOfMixedAmount)
|
||||
import Safe (atDef, maximumDef)
|
||||
import System.IO (stderr)
|
||||
import Text.CSV (parseCSVFromFile, printCSV)
|
||||
import Text.Printf (hPrintf)
|
||||
import Text.RegexPR (matchRegexPR, gsubRegexPR)
|
||||
import Data.Maybe
|
||||
import Hledger.Data.Dates (firstJust, showDate, parsedate)
|
||||
import System.Locale (defaultTimeLocale)
|
||||
import Data.Time.Format (parseTime)
|
||||
import Control.Monad (when, guard, liftM)
|
||||
import Data.Maybe
|
||||
import Data.Time.Format (parseTime)
|
||||
import Hledger.Data.Dates (firstJust, showDate, parsedate)
|
||||
import Safe (atDef, maximumDef)
|
||||
import Safe (readDef, readMay)
|
||||
import System.Directory (doesFileExist)
|
||||
import System.Exit (exitFailure)
|
||||
import System.FilePath (takeBaseName, replaceExtension)
|
||||
import Text.ParserCombinators.Parsec
|
||||
import System.IO (stderr)
|
||||
import System.Locale (defaultTimeLocale)
|
||||
import Test.HUnit
|
||||
import Text.CSV (parseCSVFromFile, printCSV)
|
||||
import Text.ParserCombinators.Parsec
|
||||
import Text.Printf (hPrintf)
|
||||
import Text.RegexPR (matchRegexPR, gsubRegexPR)
|
||||
|
||||
import Hledger.Cli.Options (Opt(Debug), progname_cli)
|
||||
import Hledger.Cli.Version (progversionstr)
|
||||
import Hledger.Data (Journal,AccountName,Transaction(..),Posting(..),PostingType(..))
|
||||
import Hledger.Data.Amount (nullmixedamt, costOfMixedAmount)
|
||||
import Hledger.Data.Journal (nullctx)
|
||||
import Hledger.Read.JournalReader (someamount,ledgeraccountname)
|
||||
import Hledger.Utils (strip, spacenonewline, restofline, parseWithCtx, assertParse, assertParseEqual, error')
|
||||
|
||||
{- |
|
||||
A set of data definitions and account-matching patterns sufficient to
|
||||
|
||||
@ -7,10 +7,16 @@ Print a histogram report.
|
||||
|
||||
module Hledger.Cli.Histogram
|
||||
where
|
||||
import Hledger.Data
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Ord
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Data
|
||||
import Hledger.Utils
|
||||
import Prelude hiding (putStr)
|
||||
import Hledger.Data.UTF8 (putStr)
|
||||
import Hledger.Utils.UTF8 (putStr)
|
||||
|
||||
|
||||
barchar = '*'
|
||||
|
||||
@ -39,12 +39,13 @@ See "Hledger.Data.Ledger" for more examples.
|
||||
|
||||
module Hledger.Cli.Main where
|
||||
|
||||
import Prelude hiding (putStr, putStrLn)
|
||||
import Hledger.Data.UTF8 (putStr, putStrLn)
|
||||
import Hledger.Data
|
||||
import Data.List
|
||||
|
||||
import Hledger.Cli
|
||||
import Hledger.Cli.Tests
|
||||
import Hledger.Cli.Version (progversionstr, binaryfilename)
|
||||
import Prelude hiding (putStr, putStrLn)
|
||||
import Hledger.Utils.UTF8 (putStr, putStrLn)
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
|
||||
@ -4,13 +4,19 @@ Command-line options for the application.
|
||||
|
||||
module Hledger.Cli.Options
|
||||
where
|
||||
import Data.Char (toLower)
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.LocalTime
|
||||
import System.Console.GetOpt
|
||||
import System.Environment
|
||||
import Test.HUnit
|
||||
import Text.RegexPR
|
||||
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Dates
|
||||
import Hledger.Data
|
||||
import Hledger.Read (myJournalPath, myTimelogPath)
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
progname_cli = "hledger"
|
||||
|
||||
@ -12,10 +12,14 @@ module Hledger.Cli.Print (
|
||||
,journalReport
|
||||
,showTransactions
|
||||
) where
|
||||
import Data.List
|
||||
import Data.Ord
|
||||
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Data
|
||||
import Hledger.Utils
|
||||
import Prelude hiding (putStr)
|
||||
import Hledger.Data.UTF8 (putStr)
|
||||
import Hledger.Utils.UTF8 (putStr)
|
||||
|
||||
|
||||
-- | A "journal report" is just a list of transactions.
|
||||
|
||||
@ -15,13 +15,21 @@ module Hledger.Cli.Register (
|
||||
,tests_Hledger_Cli_Register
|
||||
) where
|
||||
|
||||
import Control.Monad
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Ord
|
||||
import Data.Time.Calendar
|
||||
import Safe (headMay, lastMay)
|
||||
import Test.HUnit
|
||||
import Text.ParserCombinators.Parsec
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Data
|
||||
import Hledger.Utils
|
||||
import Prelude hiding (putStr)
|
||||
import Hledger.Data.UTF8 (putStr)
|
||||
import Hledger.Utils.UTF8 (putStr)
|
||||
|
||||
|
||||
-- | A register report is a list of postings to an account or set of
|
||||
|
||||
@ -7,12 +7,18 @@ Print some statistics for the journal.
|
||||
|
||||
module Hledger.Cli.Stats
|
||||
where
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Ord
|
||||
import Data.Time.Calendar
|
||||
import Text.Printf
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Hledger.Cli.Options
|
||||
import Hledger.Data
|
||||
import Hledger.Utils
|
||||
import Prelude hiding (putStr)
|
||||
import Hledger.Data.UTF8 (putStr)
|
||||
import Hledger.Utils.UTF8 (putStr)
|
||||
|
||||
|
||||
-- like Register.summarisePostings
|
||||
|
||||
@ -28,10 +28,13 @@ $ bin/hledger -f data/sample.journal balance o
|
||||
|
||||
module Hledger.Cli.Tests
|
||||
where
|
||||
import Control.Monad
|
||||
import System.Exit (exitFailure, exitWith, ExitCode(ExitSuccess)) -- base 3 compatible
|
||||
import Test.HUnit
|
||||
|
||||
import Hledger.Data -- including testing utils in Hledger.Data.Utils
|
||||
import Hledger.Cli
|
||||
import Hledger.Data
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
-- | Run unit tests.
|
||||
|
||||
@ -2,7 +2,7 @@
|
||||
{-|
|
||||
|
||||
Utilities for top-level modules and ghci. See also Hledger.Read and
|
||||
Hledger.Data.Utils.
|
||||
Hledger.Utils.
|
||||
|
||||
-}
|
||||
|
||||
@ -22,10 +22,10 @@ module Hledger.Cli.Utils
|
||||
Test(TestList),
|
||||
)
|
||||
where
|
||||
import Hledger.Data
|
||||
import Hledger.Read
|
||||
import Hledger.Cli.Options (Opt(..),journalFilePathFromOpts) -- ,optsToFilterSpec)
|
||||
import Control.Exception
|
||||
import Control.Monad
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Safe (readMay)
|
||||
import System.Directory (getModificationTime, getDirectoryContents, copyFile)
|
||||
import System.Exit
|
||||
@ -33,6 +33,14 @@ import System.FilePath ((</>), splitFileName, takeDirectory)
|
||||
import System.Info (os)
|
||||
import System.Process (readProcessWithExitCode)
|
||||
import System.Time (ClockTime, getClockTime, diffClockTimes, TimeDiff(TimeDiff))
|
||||
import Test.HUnit
|
||||
import Text.Printf
|
||||
import Text.RegexPR
|
||||
|
||||
import Hledger.Cli.Options (Opt(..),journalFilePathFromOpts)
|
||||
import Hledger.Data
|
||||
import Hledger.Read
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
-- | Parse the user's specified journal file and run a hledger command on
|
||||
|
||||
@ -10,9 +10,11 @@ module Hledger.Cli.Version (
|
||||
,binaryfilename
|
||||
)
|
||||
where
|
||||
import Data.List
|
||||
import System.Info (os, arch)
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Utils
|
||||
|
||||
|
||||
-- version and PATCHLEVEL are set by the make process
|
||||
|
||||
@ -1,7 +1,6 @@
|
||||
#!/usr/bin/env runhaskell
|
||||
-- list the default journal's chart of accounts in --flat style
|
||||
import Hledger.Read
|
||||
import Hledger.Data
|
||||
import Hledger
|
||||
main = do
|
||||
j <- myJournal
|
||||
let l = journalToLedger nullfilterspec{empty=True} j
|
||||
|
||||
Loading…
Reference in New Issue
Block a user