hlint: use getContents

This commit is contained in:
Simon Michael 2009-09-23 17:43:23 +00:00
parent a8e510d789
commit 20878df544

View File

@ -6,7 +6,7 @@ Parsers for standard ledger and timelog files.
module Ledger.Parse module Ledger.Parse
where where
import Prelude hiding (readFile, putStr, putStrLn, print) 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
@ -64,7 +64,7 @@ printParseError e = do putStr "ledger parse error at "; print e
-- let's get to it -- let's get to it
parseLedgerFile :: LocalTime -> FilePath -> ErrorT String IO RawLedger parseLedgerFile :: LocalTime -> FilePath -> ErrorT String IO RawLedger
parseLedgerFile t "-" = liftIO (hGetContents stdin) >>= parseLedger t "-" parseLedgerFile t "-" = liftIO getContents >>= parseLedger t "-"
parseLedgerFile t f = liftIO (readFile f) >>= parseLedger t f parseLedgerFile t f = liftIO (readFile f) >>= parseLedger t f
-- | Parses the contents of a ledger file, or gives an error. Requires -- | Parses the contents of a ledger file, or gives an error. Requires