Allow UTF8 in ledgers (account names, descriptions).

This patch fixes broken layout of some commands when there is Unicode
text in the ledger file.

I substituted System.IO functions with System.IO.UTF8. Now all strings
are Unicode internally, and take's and length's work correctly.
In particular, add, balance, hist, print and register commands seem
to work correctly; ui is still broken for me, I didn't try web.

I decode command line arguments from UTF8 forcefully, to permit
searches for accounts and descriptions with Unicode (otherwise, it
does not work).

The patch adds an additional dependency: utf8-string.

This patch does not include new test cases.
This commit is contained in:
Sergey Astanin 2009-05-14 20:44:06 +00:00
parent 412a39b4aa
commit 86fab58e6a
10 changed files with 25 additions and 8 deletions

View File

@ -7,10 +7,12 @@ An add command to help with data entry.
module AddCommand module AddCommand
where where
-- import Data.List.Utils (replace) -- import Data.List.Utils (replace)
import Prelude hiding (putStr, putStrLn, getLine, appendFile)
import Ledger import Ledger
import Options import Options
import RegisterCommand (showRegisterReport) import RegisterCommand (showRegisterReport)
import System.IO import System.IO.UTF8
import System.IO (stderr, hFlush)
import System.IO.Error import System.IO.Error
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import Utils (ledgerFromStringWithOpts) import Utils (ledgerFromStringWithOpts)

View File

@ -96,6 +96,7 @@ balance report:
module BalanceCommand module BalanceCommand
where where
import Prelude hiding (putStr)
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Ledger.Amount import Ledger.Amount
@ -105,6 +106,7 @@ import Ledger.Ledger
import Ledger.Parse import Ledger.Parse
import Options import Options
import Utils import Utils
import System.IO.UTF8
-- | Print a balance report. -- | Print a balance report.

View File

@ -6,10 +6,12 @@ Print a histogram report.
module HistogramCommand module HistogramCommand
where where
import Prelude hiding (putStr)
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Map ((!)) import Data.Map ((!))
import Ledger import Ledger
import Options import Options
import System.IO.UTF8
barchar = '*' barchar = '*'
@ -43,4 +45,4 @@ countBar ts = replicate (length ts) barchar
total ts = show $ sumTransactions ts total ts = show $ sumTransactions ts
-- totalBar ts = replicate (sumTransactions ts) barchar -- totalBar ts = replicate (sumTransactions ts) barchar

View File

@ -6,6 +6,7 @@ Parsers for standard ledger and timelog files.
module Ledger.Parse module Ledger.Parse
where where
import Prelude hiding (readFile, putStr, print)
import Control.Monad import Control.Monad
import Control.Monad.Error import Control.Monad.Error
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
@ -14,7 +15,8 @@ import Text.ParserCombinators.Parsec.Language
import Text.ParserCombinators.Parsec.Combinator import Text.ParserCombinators.Parsec.Combinator
import qualified Text.ParserCombinators.Parsec.Token as P import qualified Text.ParserCombinators.Parsec.Token as P
import System.Directory import System.Directory
import System.IO import System.IO.UTF8
import System.IO (stdin)
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Time.LocalTime import Data.Time.LocalTime
import Data.Time.Calendar import Data.Time.Calendar

View File

@ -23,6 +23,7 @@ module Text.Regex,
module Test.HUnit, module Test.HUnit,
) )
where where
import Prelude hiding (readFile)
import Char import Char
import Control.Exception import Control.Exception
import Control.Monad import Control.Monad
@ -35,7 +36,7 @@ import Data.Time.Clock
import Data.Time.Calendar import Data.Time.Calendar
import Data.Time.LocalTime import Data.Time.LocalTime
import Debug.Trace import Debug.Trace
import System.IO import System.IO.UTF8
import Test.HUnit import Test.HUnit
import Text.Printf import Text.Printf
import Text.Regex import Text.Regex

View File

@ -18,6 +18,8 @@ import Ledger.Parse
import Ledger.Utils import Ledger.Utils
import Ledger.Types import Ledger.Types
import Ledger.Dates import Ledger.Dates
import Codec.Binary.UTF8.String (decodeString)
import Control.Monad (liftM)
progname = "hledger" progname = "hledger"
timeprogname = "hours" 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. -- as \"hours\", the -f $TIMELOG -p today options are assumed as a default.
parseArguments :: IO ([Opt], String, [String]) parseArguments :: IO ([Opt], String, [String])
parseArguments = do parseArguments = do
args <- getArgs args <- liftM (map decodeString) getArgs
let (os,as,es) = getOpt Permute options args let (os,as,es) = getOpt Permute options args
istimequery <- usingTimeProgramName istimequery <- usingTimeProgramName
let os' = if istimequery then (Period "today"):os else os let os' = if istimequery then (Period "today"):os else os

View File

@ -6,8 +6,10 @@ A ledger-compatible @print@ command.
module PrintCommand module PrintCommand
where where
import Prelude hiding (putStr)
import Ledger import Ledger
import Options import Options
import System.IO.UTF8
-- | Print ledger transactions in standard format. -- | Print ledger transactions in standard format.

View File

@ -6,10 +6,12 @@ A ledger-compatible @register@ command.
module RegisterCommand module RegisterCommand
where where
import Prelude hiding (putStr)
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Map ((!)) import Data.Map ((!))
import Ledger import Ledger
import Options import Options
import System.IO.UTF8
-- | Print a register report. -- | Print a register report.

View File

@ -28,7 +28,7 @@ Flag happs
Library Library
Build-Depends: base, containers, haskell98, directory, parsec, regex-compat, Build-Depends: base, containers, haskell98, directory, parsec, regex-compat,
old-locale, time, HUnit, filepath old-locale, time, HUnit, filepath, utf8-string
Exposed-modules:Ledger Exposed-modules:Ledger
Ledger.Account Ledger.Account
@ -53,7 +53,7 @@ Executable hledger
Build-Depends: base, containers, haskell98, directory, parsec, Build-Depends: base, containers, haskell98, directory, parsec,
regex-compat, regexpr>=0.5.1, old-locale, time, regex-compat, regexpr>=0.5.1, old-locale, time,
HUnit, mtl, bytestring, filepath, process, testpack, HUnit, mtl, bytestring, filepath, process, testpack,
regex-pcre, csv, split regex-pcre, csv, split, utf8-string
Other-Modules: Other-Modules:
BalanceCommand BalanceCommand

View File

@ -51,9 +51,11 @@ module Main (
#endif #endif
) )
where where
import Prelude hiding (putStr)
import Control.Monad.Error import Control.Monad.Error
import qualified Data.Map as Map (lookup) import qualified Data.Map as Map (lookup)
import System.IO import System.IO.UTF8
import System.IO (stderr)
import Version (versionmsg) import Version (versionmsg)
import Ledger import Ledger