More IO functions

Ignore-this: e118f2be06c7c911034b937de28a9549

darcs-hash:20090829135432-a4fee-7d2652ba7654d21d147388929b6864817e327428
This commit is contained in:
Henning Guenther 2009-08-29 06:54:32 -07:00
parent f7b6c800ef
commit 44d37e6bea

View File

@ -1,27 +1,64 @@
{-# LANGUAGE ImplicitParams,ForeignFunctionInterface #-}
{- | This module provides a replacement for the normal (unicode unaware) IO functions of haskell.
By using implicit parameters, it can be used almost as a drop-in replacement.
For example, consider the following simple echo program:
> main = do
> str <- getContents
> putStr str
To make this program process UTF-8 data, change the program to:
> {-# LANGUAGE ImplicitParams #-}
>
> import Prelude hiding (getContents,putStr)
> import System.IO.Encoding
> import Data.Encoding.UTF8
>
> main = do
> let ?enc = UTF8
> str <- getContents
> putStr str
Or, if you want to use the standard system encoding:
> {-# LANGUAGE ImplicitParams #-}
>
> import Prelude hiding (getContents,putStr)
> import System.IO.Encoding
>
> main = do
> e <- getSystemEncoding
> let ?enc = e
> str <- getContents
> putStr str
-}
module System.IO.Encoding
(getSystemEncoding
,getContents
,putStr
,putStrLn
,hPutStr
,hPutStrLn
,hGetContents
,readFile
,writeFile
,appendFile
,getChar
,hGetChar
,getLine
,hGetLine
,putChar
,hPutChar
,interact
,print) where
,print
,hPrint) where
import Foreign.C.String
import Data.Encoding
import System.IO (Handle,stdout,stdin)
import Prelude hiding (print,getContents,readFile,writeFile,appendFile,interact)
import Prelude hiding (print,getContents,readFile,writeFile,appendFile,interact,putStr,putStrLn,getChar,getLine,putChar)
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString as BS
import Control.Monad.Reader (runReaderT)
@ -38,6 +75,12 @@ getContents = do
str <- LBS.getContents
return $ decodeLazyByteString ?enc str
putStr :: (Encoding e,?enc :: e) => String -> IO ()
putStr = hPutStr stdout
putStrLn :: (Encoding e,?enc :: e) => String -> IO ()
putStrLn = hPutStrLn stdout
-- | Like the normal 'System.IO.hPutStr', but encodes the output using an
-- encoding.
hPutStr :: (Encoding e,?enc :: e) => Handle -> String -> IO ()
@ -49,7 +92,10 @@ hPutStrLn h str = do
LBS.hPut h (encodeLazyByteString ?enc "\n")
print :: (Encoding e,Show a,?enc :: e) => a -> IO ()
print x = hPutStrLn stdout (show x)
print = hPrint stdout
hPrint :: (Encoding e,Show a,?enc :: e) => Handle -> a -> IO ()
hPrint h x = hPutStrLn h (show x)
readFile :: (Encoding e,?enc :: e) => FilePath -> IO String
readFile fn = LBS.readFile fn >>= return.(decodeLazyByteString ?enc)
@ -60,14 +106,23 @@ writeFile fn str = LBS.writeFile fn $ encodeLazyByteString ?enc str
appendFile :: (Encoding e,?enc :: e) => FilePath -> String -> IO ()
appendFile fn str = LBS.appendFile fn $ encodeLazyByteString ?enc str
getChar :: (Encoding e,?enc :: e) => IO Char
getChar = hGetChar stdin
hGetChar :: (Encoding e,?enc :: e) => Handle -> IO Char
hGetChar h = runReaderT (decodeChar ?enc) h
getLine :: (Encoding e,?enc :: e) => IO String
getLine = hGetLine stdin
hGetLine :: (Encoding e,?enc :: e) => Handle -> IO String
hGetLine h = do
line <- BS.hGetLine h
return $ decodeStrictByteString ?enc line
putChar :: (Encoding e,?enc :: e) => Char -> IO ()
putChar = hPutChar stdout
hPutChar :: (Encoding e,?enc :: e) => Handle -> Char -> IO ()
hPutChar h c = runReaderT (encodeChar ?enc c) h