GHC 6.12.1 has UTF8 support on board. Using System.IO.UTF8 can cause problems.
Therefore use System.IO.UTF8 only on previous versions. Testet with GHC 6.10.4 and 6.12.1
This commit is contained in:
		
							parent
							
								
									bd1c8444f4
								
							
						
					
					
						commit
						8937ed457d
					
				| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-|  | {-|  | ||||||
| 
 | 
 | ||||||
| A history-aware add command to help with data entry. | A history-aware add command to help with data entry. | ||||||
| @ -6,12 +7,16 @@ A history-aware add command to help with data entry. | |||||||
| 
 | 
 | ||||||
| module Commands.Add | module Commands.Add | ||||||
| where | where | ||||||
| import Prelude hiding (putStr, putStrLn, getLine, appendFile) |  | ||||||
| import Ledger | import Ledger | ||||||
| import Options | import Options | ||||||
| import Commands.Register (showRegisterReport) | import Commands.Register (showRegisterReport) | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|  | import Prelude hiding (putStr, putStrLn, getLine, appendFile) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
| import System.IO (stderr, hFlush) | import System.IO ( stderr, hFlush ) | ||||||
|  | #else | ||||||
|  | import System.IO ( stderr, hFlush, hPutStrLn, hPutStr ) | ||||||
|  | #endif | ||||||
| import System.IO.Error | import System.IO.Error | ||||||
| import Text.ParserCombinators.Parsec | import Text.ParserCombinators.Parsec | ||||||
| import Utils (ledgerFromStringWithOpts) | import Utils (ledgerFromStringWithOpts) | ||||||
| @ -24,9 +29,9 @@ add :: [Opt] -> [String] -> Ledger -> IO () | |||||||
| add opts args l | add opts args l | ||||||
|     | filepath (journal l) == "-" = return () |     | filepath (journal l) == "-" = return () | ||||||
|     | otherwise = do |     | otherwise = do | ||||||
|   hPutStrLn stderr |   hPutStrLn stderr $ | ||||||
|     "Enter one or more transactions, which will be added to your ledger file.\n\ |     "Enter one or more transactions, which will be added to your ledger file.\n" | ||||||
|     \To complete a transaction, enter . as account name. To quit, press control-c." |     ++"To complete a transaction, enter . as account name. To quit, press control-c." | ||||||
|   today <- getCurrentDay |   today <- getCurrentDay | ||||||
|   getAndAddTransactions l opts args today `catch` (\e -> unless (isEOFError e) $ ioError e) |   getAndAddTransactions l opts args today `catch` (\e -> unless (isEOFError e) $ ioError e) | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| A ledger-compatible @balance@ command. | A ledger-compatible @balance@ command. | ||||||
| @ -96,7 +97,6 @@ balance report: | |||||||
| 
 | 
 | ||||||
| module Commands.Balance | module Commands.Balance | ||||||
| where | where | ||||||
| import Prelude hiding (putStr) |  | ||||||
| import Ledger.Utils | import Ledger.Utils | ||||||
| import Ledger.Types | import Ledger.Types | ||||||
| import Ledger.Amount | import Ledger.Amount | ||||||
| @ -104,7 +104,10 @@ import Ledger.AccountName | |||||||
| import Ledger.Posting | import Ledger.Posting | ||||||
| import Ledger.Ledger | import Ledger.Ledger | ||||||
| import Options | import Options | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|  | import Prelude hiding ( putStr ) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| -- | Print a balance report. | -- | Print a balance report. | ||||||
|  | |||||||
| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-|  | {-|  | ||||||
| 
 | 
 | ||||||
| Print a histogram report. | Print a histogram report. | ||||||
| @ -6,10 +7,12 @@ Print a histogram report. | |||||||
| 
 | 
 | ||||||
| module Commands.Histogram | module Commands.Histogram | ||||||
| where | where | ||||||
| import Prelude hiding (putStr) |  | ||||||
| import Ledger | import Ledger | ||||||
| import Options | import Options | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|  | import Prelude hiding ( putStr ) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| barchar = '*' | barchar = '*' | ||||||
|  | |||||||
| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-|  | {-|  | ||||||
| 
 | 
 | ||||||
| A ledger-compatible @print@ command. | A ledger-compatible @print@ command. | ||||||
| @ -6,10 +7,12 @@ A ledger-compatible @print@ command. | |||||||
| 
 | 
 | ||||||
| module Commands.Print | module Commands.Print | ||||||
| where | where | ||||||
| import Prelude hiding (putStr) |  | ||||||
| import Ledger | import Ledger | ||||||
| import Options | import Options | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|  | import Prelude hiding ( putStr ) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| -- | Print ledger transactions in standard format. | -- | Print ledger transactions in standard format. | ||||||
|  | |||||||
| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-|  | {-|  | ||||||
| 
 | 
 | ||||||
| A ledger-compatible @register@ command. | A ledger-compatible @register@ command. | ||||||
| @ -6,10 +7,12 @@ A ledger-compatible @register@ command. | |||||||
| 
 | 
 | ||||||
| module Commands.Register | module Commands.Register | ||||||
| where | where | ||||||
| import Prelude hiding (putStr) |  | ||||||
| import Ledger | import Ledger | ||||||
| import Options | import Options | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|  | import Prelude hiding ( putStr ) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| -- | Print a register report. | -- | Print a register report. | ||||||
|  | |||||||
| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| Print some statistics for the ledger. | Print some statistics for the ledger. | ||||||
| @ -6,10 +7,12 @@ Print some statistics for the ledger. | |||||||
| 
 | 
 | ||||||
| module Commands.Stats | module Commands.Stats | ||||||
| where | where | ||||||
| import Prelude hiding (putStr) |  | ||||||
| import Ledger | import Ledger | ||||||
| import Options | import Options | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|  | import Prelude hiding ( putStr ) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| -- | Print various statistics for the ledger. | -- | Print various statistics for the ledger. | ||||||
|  | |||||||
| @ -6,7 +6,9 @@ A web-based UI. | |||||||
| 
 | 
 | ||||||
| module Commands.Web | module Commands.Web | ||||||
| where | where | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
| import Codec.Binary.UTF8.String (decodeString) | import Codec.Binary.UTF8.String (decodeString) | ||||||
|  | #endif | ||||||
| import Control.Applicative.Error (Failing(Success,Failure)) | import Control.Applicative.Error (Failing(Success,Failure)) | ||||||
| import Control.Concurrent | import Control.Concurrent | ||||||
| import Control.Monad.Reader (ask) | import Control.Monad.Reader (ask) | ||||||
| @ -50,7 +52,7 @@ import Commands.Register | |||||||
| import Ledger | import Ledger | ||||||
| import Utils (openBrowserOn) | import Utils (openBrowserOn) | ||||||
| import Ledger.IO (readLedger) | import Ledger.IO (readLedger) | ||||||
| 
 | #  | ||||||
| -- import Debug.Trace | -- import Debug.Trace | ||||||
| -- strace :: Show a => a -> a | -- strace :: Show a => a -> a | ||||||
| -- strace a = trace (show a) a | -- strace a = trace (show a) a | ||||||
| @ -244,8 +246,13 @@ searchform env = do | |||||||
| addform :: Hack.Env -> HSP XML | addform :: Hack.Env -> HSP XML | ||||||
| addform env = do | addform env = do | ||||||
|   let inputs = Hack.Contrib.Request.inputs env |   let inputs = Hack.Contrib.Request.inputs env | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|       date  = decodeString $ fromMaybe "" $ lookup "date"  inputs |       date  = decodeString $ fromMaybe "" $ lookup "date"  inputs | ||||||
|       desc  = decodeString $ fromMaybe "" $ lookup "desc"  inputs |       desc  = decodeString $ fromMaybe "" $ lookup "desc"  inputs | ||||||
|  | #else | ||||||
|  |       date  = fromMaybe "" $ lookup "date"  inputs | ||||||
|  |       desc  = fromMaybe "" $ lookup "desc"  inputs | ||||||
|  | #endif | ||||||
|   <div> |   <div> | ||||||
|    <div id="addform"> |    <div id="addform"> | ||||||
|    <form action="" method="POST"> |    <form action="" method="POST"> | ||||||
| @ -268,8 +275,13 @@ addform env = do | |||||||
| transactionfields :: Int -> Hack.Env -> HSP XML | transactionfields :: Int -> Hack.Env -> HSP XML | ||||||
| transactionfields n env = do | transactionfields n env = do | ||||||
|   let inputs = Hack.Contrib.Request.inputs env |   let inputs = Hack.Contrib.Request.inputs env | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|       acct = decodeString $ fromMaybe "" $ lookup acctvar inputs |       acct = decodeString $ fromMaybe "" $ lookup acctvar inputs | ||||||
|       amt  = decodeString $ fromMaybe "" $ lookup amtvar  inputs |       amt  = decodeString $ fromMaybe "" $ lookup amtvar  inputs | ||||||
|  | #else | ||||||
|  |       acct = fromMaybe "" $ lookup acctvar inputs | ||||||
|  |       amt  = fromMaybe "" $ lookup amtvar  inputs | ||||||
|  | #endif | ||||||
|   <tr> |   <tr> | ||||||
|     <td> |     <td> | ||||||
|       [NBSP][NBSP] |       [NBSP][NBSP] | ||||||
| @ -292,12 +304,21 @@ handleAddform l = do | |||||||
|     validate :: Hack.Env -> Day -> Failing Transaction |     validate :: Hack.Env -> Day -> Failing Transaction | ||||||
|     validate env today = |     validate env today = | ||||||
|         let inputs = Hack.Contrib.Request.inputs env |         let inputs = Hack.Contrib.Request.inputs env | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|             date  = decodeString $ fromMaybe "today" $ lookup "date"  inputs |             date  = decodeString $ fromMaybe "today" $ lookup "date"  inputs | ||||||
|             desc  = decodeString $ fromMaybe "" $ lookup "desc"  inputs |             desc  = decodeString $ fromMaybe "" $ lookup "desc"  inputs | ||||||
|             acct1 = decodeString $ fromMaybe "" $ lookup "acct1" inputs |             acct1 = decodeString $ fromMaybe "" $ lookup "acct1" inputs | ||||||
|             amt1  = decodeString $ fromMaybe "" $ lookup "amt1"  inputs |             amt1  = decodeString $ fromMaybe "" $ lookup "amt1"  inputs | ||||||
|             acct2 = decodeString $ fromMaybe "" $ lookup "acct2" inputs |             acct2 = decodeString $ fromMaybe "" $ lookup "acct2" inputs | ||||||
|             amt2  = decodeString $ fromMaybe "" $ lookup "amt2"  inputs |             amt2  = decodeString $ fromMaybe "" $ lookup "amt2"  inputs | ||||||
|  | #else | ||||||
|  |             date  = fromMaybe "today" $ lookup "date"  inputs | ||||||
|  |             desc  = fromMaybe "" $ lookup "desc"  inputs | ||||||
|  |             acct1 = fromMaybe "" $ lookup "acct1" inputs | ||||||
|  |             amt1  = fromMaybe "" $ lookup "amt1"  inputs | ||||||
|  |             acct2 = fromMaybe "" $ lookup "acct2" inputs | ||||||
|  |             amt2  = fromMaybe "" $ lookup "amt2"  inputs | ||||||
|  | #endif | ||||||
|             validateDate ""  = ["missing date"] |             validateDate ""  = ["missing date"] | ||||||
|             validateDate _   = [] |             validateDate _   = [] | ||||||
|             validateDesc ""  = ["missing description"] |             validateDesc ""  = ["missing description"] | ||||||
|  | |||||||
| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-| | {-| | ||||||
| Utilities for doing I/O with ledger files. | Utilities for doing I/O with ledger files. | ||||||
| -} | -} | ||||||
| @ -12,8 +13,10 @@ import Ledger.Utils (getCurrentLocalTime) | |||||||
| import Ledger.Dates (nulldatespan) | import Ledger.Dates (nulldatespan) | ||||||
| import System.Directory (getHomeDirectory) | import System.Directory (getHomeDirectory) | ||||||
| import System.Environment (getEnv) | import System.Environment (getEnv) | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
| import Prelude hiding (readFile) | import Prelude hiding (readFile) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| import System.FilePath ((</>)) | import System.FilePath ((</>)) | ||||||
| import System.Time (getClockTime) | import System.Time (getClockTime) | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| Parsers for standard ledger and timelog files. | Parsers for standard ledger and timelog files. | ||||||
| @ -6,13 +7,15 @@ Parsers for standard ledger and timelog files. | |||||||
| 
 | 
 | ||||||
| module Ledger.Parse | module Ledger.Parse | ||||||
| where | where | ||||||
| import Prelude hiding (readFile, putStr, putStrLn, print, getContents) |  | ||||||
| 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 | ||||||
| import Text.ParserCombinators.Parsec.Char | import Text.ParserCombinators.Parsec.Char | ||||||
| import Text.ParserCombinators.Parsec.Combinator | import Text.ParserCombinators.Parsec.Combinator | ||||||
| import System.Directory | import System.Directory | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|  | import Prelude hiding (readFile, putStr, putStrLn, print, getContents) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| import Ledger.Utils | import Ledger.Utils | ||||||
| import Ledger.Types | import Ledger.Types | ||||||
| import Ledger.Dates | import Ledger.Dates | ||||||
|  | |||||||
| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| Provide standard imports and utilities which are useful everywhere, or | Provide standard imports and utilities which are useful everywhere, or | ||||||
| @ -23,7 +24,6 @@ module Text.RegexPR, | |||||||
| 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 | ||||||
| @ -36,7 +36,10 @@ 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 | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|  | import Prelude hiding (readFile) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| import Test.HUnit | import Test.HUnit | ||||||
| import Text.Printf | import Text.Printf | ||||||
| import Text.RegexPR | import Text.RegexPR | ||||||
|  | |||||||
| @ -11,7 +11,9 @@ import Ledger.IO (myLedgerPath,myTimelogPath) | |||||||
| import Ledger.Utils | import Ledger.Utils | ||||||
| import Ledger.Types | import Ledger.Types | ||||||
| import Ledger.Dates | import Ledger.Dates | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
| import Codec.Binary.UTF8.String (decodeString) | import Codec.Binary.UTF8.String (decodeString) | ||||||
|  | #endif | ||||||
| import Control.Monad (liftM) | import Control.Monad (liftM) | ||||||
| 
 | 
 | ||||||
| progname      = "hledger" | progname      = "hledger" | ||||||
| @ -149,7 +151,11 @@ optValuesForConstructors fs opts = concatMap get opts | |||||||
| -- YYYY/MM/DD format based on the current time. | -- YYYY/MM/DD format based on the current time. | ||||||
| parseArguments :: IO ([Opt], String, [String]) | parseArguments :: IO ([Opt], String, [String]) | ||||||
| parseArguments = do | parseArguments = do | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
|   args <- liftM (map decodeString) getArgs |   args <- liftM (map decodeString) getArgs | ||||||
|  | #else | ||||||
|  |   args <- getArgs | ||||||
|  | #endif | ||||||
|   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 | ||||||
|  | |||||||
							
								
								
									
										5
									
								
								Utils.hs
									
									
									
									
									
								
							
							
						
						
									
										5
									
								
								Utils.hs
									
									
									
									
									
								
							| @ -1,3 +1,4 @@ | |||||||
|  | {-# LANGUAGE CPP #-} | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| Utilities for top-level modules and ghci. See also "Ledger.IO" and | Utilities for top-level modules and ghci. See also "Ledger.IO" and | ||||||
| @ -12,7 +13,11 @@ import Ledger | |||||||
| import Options (Opt(..),ledgerFilePathFromOpts) -- ,optsToFilterSpec) | import Options (Opt(..),ledgerFilePathFromOpts) -- ,optsToFilterSpec) | ||||||
| import System.Directory (doesFileExist) | import System.Directory (doesFileExist) | ||||||
| import System.IO (stderr) | import System.IO (stderr) | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
| import System.IO.UTF8 (hPutStrLn) | import System.IO.UTF8 (hPutStrLn) | ||||||
|  | #else | ||||||
|  | import System.IO (hPutStrLn) | ||||||
|  | #endif | ||||||
| import System.Exit | import System.Exit | ||||||
| import System.Cmd (system) | import System.Cmd (system) | ||||||
| import System.Info (os) | import System.Info (os) | ||||||
|  | |||||||
| @ -36,8 +36,10 @@ See "Ledger.Ledger" for more examples. | |||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
| module Main where | module Main where | ||||||
|  | #if __GLASGOW_HASKELL__ <= 610 | ||||||
| import Prelude hiding (putStr, putStrLn) | import Prelude hiding (putStr, putStrLn) | ||||||
| import System.IO.UTF8 | import System.IO.UTF8 | ||||||
|  | #endif | ||||||
| 
 | 
 | ||||||
| import Commands.All | import Commands.All | ||||||
| import Ledger | import Ledger | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user