Safe Haskell | None |
---|---|
Language | Haskell98 |
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:
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:
import Prelude hiding (getContents,putStr) import System.IO.Encoding main = do e <- getSystemEncoding let ?enc = e str <- getContents putStr str
- getSystemEncoding :: IO DynEncoding
- getContents :: (Encoding e, ?enc :: e) => IO String
- putStr :: (Encoding e, ?enc :: e) => String -> IO ()
- putStrLn :: (Encoding e, ?enc :: e) => String -> IO ()
- hPutStr :: (Encoding e, ?enc :: e) => Handle -> String -> IO ()
- hPutStrLn :: (Encoding e, ?enc :: e) => Handle -> String -> IO ()
- hGetContents :: (Encoding e, ?enc :: e) => Handle -> IO String
- readFile :: (Encoding e, ?enc :: e) => FilePath -> IO String
- writeFile :: (Encoding e, ?enc :: e) => FilePath -> String -> IO ()
- appendFile :: (Encoding e, ?enc :: e) => FilePath -> String -> IO ()
- getChar :: (Encoding e, ?enc :: e) => IO Char
- hGetChar :: (Encoding e, ?enc :: e) => Handle -> IO Char
- getLine :: (Encoding e, ?enc :: e) => IO String
- hGetLine :: (Encoding e, ?enc :: e) => Handle -> IO String
- putChar :: (Encoding e, ?enc :: e) => Char -> IO ()
- hPutChar :: (Encoding e, ?enc :: e) => Handle -> Char -> IO ()
- interact :: (Encoding e, ?enc :: e) => (String -> String) -> IO ()
- print :: (Encoding e, Show a, ?enc :: e) => a -> IO ()
- hPrint :: (Encoding e, Show a, ?enc :: e) => Handle -> a -> IO ()
Documentation
getSystemEncoding :: IO DynEncoding Source #
Returns the encoding used on the current system. Currently only supported on Linux-alikes.
hPutStr :: (Encoding e, ?enc :: e) => Handle -> String -> IO () Source #
Like the normal hPutStr
, but encodes the output using an
encoding.
hGetContents :: (Encoding e, ?enc :: e) => Handle -> IO String Source #
Like the normal hGetContents
, but decodes the input using an
encoding.