diff --git a/AddCommand.hs b/AddCommand.hs index 6a723f465..dd9d3d11a 100644 --- a/AddCommand.hs +++ b/AddCommand.hs @@ -7,10 +7,12 @@ An add command to help with data entry. module AddCommand where -- import Data.List.Utils (replace) +import Prelude hiding (putStr, putStrLn, getLine, appendFile) import Ledger import Options import RegisterCommand (showRegisterReport) -import System.IO +import System.IO.UTF8 +import System.IO (stderr, hFlush) import System.IO.Error import Text.ParserCombinators.Parsec import Utils (ledgerFromStringWithOpts) diff --git a/BalanceCommand.hs b/BalanceCommand.hs index 9b8e3b67b..cf546113b 100644 --- a/BalanceCommand.hs +++ b/BalanceCommand.hs @@ -96,6 +96,7 @@ balance report: module BalanceCommand where +import Prelude hiding (putStr) import Ledger.Utils import Ledger.Types import Ledger.Amount @@ -105,6 +106,7 @@ import Ledger.Ledger import Ledger.Parse import Options import Utils +import System.IO.UTF8 -- | Print a balance report. diff --git a/HistogramCommand.hs b/HistogramCommand.hs index 8e543b191..d24ee246f 100644 --- a/HistogramCommand.hs +++ b/HistogramCommand.hs @@ -6,10 +6,12 @@ Print a histogram report. module HistogramCommand where +import Prelude hiding (putStr) import qualified Data.Map as Map import Data.Map ((!)) import Ledger import Options +import System.IO.UTF8 barchar = '*' @@ -43,4 +45,4 @@ countBar ts = replicate (length ts) barchar total ts = show $ sumTransactions ts --- totalBar ts = replicate (sumTransactions ts) barchar \ No newline at end of file +-- totalBar ts = replicate (sumTransactions ts) barchar diff --git a/Ledger/Parse.hs b/Ledger/Parse.hs index 47b61b187..fc806b41e 100644 --- a/Ledger/Parse.hs +++ b/Ledger/Parse.hs @@ -6,6 +6,7 @@ Parsers for standard ledger and timelog files. module Ledger.Parse where +import Prelude hiding (readFile, putStr, print) import Control.Monad import Control.Monad.Error import Text.ParserCombinators.Parsec @@ -14,7 +15,8 @@ import Text.ParserCombinators.Parsec.Language import Text.ParserCombinators.Parsec.Combinator import qualified Text.ParserCombinators.Parsec.Token as P import System.Directory -import System.IO +import System.IO.UTF8 +import System.IO (stdin) import qualified Data.Map as Map import Data.Time.LocalTime import Data.Time.Calendar diff --git a/Ledger/Utils.hs b/Ledger/Utils.hs index aad8f15f4..ab10450c7 100644 --- a/Ledger/Utils.hs +++ b/Ledger/Utils.hs @@ -23,6 +23,7 @@ module Text.Regex, module Test.HUnit, ) where +import Prelude hiding (readFile) import Char import Control.Exception import Control.Monad @@ -35,7 +36,7 @@ import Data.Time.Clock import Data.Time.Calendar import Data.Time.LocalTime import Debug.Trace -import System.IO +import System.IO.UTF8 import Test.HUnit import Text.Printf import Text.Regex diff --git a/Options.hs b/Options.hs index 6dcdada70..07d13a3d9 100644 --- a/Options.hs +++ b/Options.hs @@ -18,6 +18,8 @@ import Ledger.Parse import Ledger.Utils import Ledger.Types import Ledger.Dates +import Codec.Binary.UTF8.String (decodeString) +import Control.Monad (liftM) progname = "hledger" timeprogname = "hours" @@ -137,7 +139,7 @@ optValuesForConstructors fs opts = concatMap get opts -- as \"hours\", the -f $TIMELOG -p today options are assumed as a default. parseArguments :: IO ([Opt], String, [String]) parseArguments = do - args <- getArgs + args <- liftM (map decodeString) getArgs let (os,as,es) = getOpt Permute options args istimequery <- usingTimeProgramName let os' = if istimequery then (Period "today"):os else os diff --git a/PrintCommand.hs b/PrintCommand.hs index 75eea30d6..5d81aec64 100644 --- a/PrintCommand.hs +++ b/PrintCommand.hs @@ -6,8 +6,10 @@ A ledger-compatible @print@ command. module PrintCommand where +import Prelude hiding (putStr) import Ledger import Options +import System.IO.UTF8 -- | Print ledger transactions in standard format. diff --git a/RegisterCommand.hs b/RegisterCommand.hs index 46778eb69..38280e285 100644 --- a/RegisterCommand.hs +++ b/RegisterCommand.hs @@ -6,10 +6,12 @@ A ledger-compatible @register@ command. module RegisterCommand where +import Prelude hiding (putStr) import qualified Data.Map as Map import Data.Map ((!)) import Ledger import Options +import System.IO.UTF8 -- | Print a register report. diff --git a/hledger.cabal b/hledger.cabal index 603b10f4b..39ccd8942 100644 --- a/hledger.cabal +++ b/hledger.cabal @@ -28,7 +28,7 @@ Flag happs Library Build-Depends: base, containers, haskell98, directory, parsec, regex-compat, - old-locale, time, HUnit, filepath + old-locale, time, HUnit, filepath, utf8-string Exposed-modules:Ledger Ledger.Account @@ -53,7 +53,7 @@ Executable hledger Build-Depends: base, containers, haskell98, directory, parsec, regex-compat, regexpr>=0.5.1, old-locale, time, HUnit, mtl, bytestring, filepath, process, testpack, - regex-pcre, csv, split + regex-pcre, csv, split, utf8-string Other-Modules: BalanceCommand diff --git a/hledger.hs b/hledger.hs index 5051e2b10..f69b1a82e 100644 --- a/hledger.hs +++ b/hledger.hs @@ -51,9 +51,11 @@ module Main ( #endif ) where +import Prelude hiding (putStr) import Control.Monad.Error import qualified Data.Map as Map (lookup) -import System.IO +import System.IO.UTF8 +import System.IO (stderr) import Version (versionmsg) import Ledger