encoding-0.8: A library for various character encodings

Safe HaskellNone
LanguageHaskell98

System.IO.Encoding

Description

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     

Synopsis

Documentation

getSystemEncoding :: IO DynEncoding Source

Returns the encoding used on the current system. Currently only supported on Linux-alikes.

getContents :: (Encoding e, ?enc :: e) => IO String Source

putStr :: (Encoding e, ?enc :: e) => String -> IO () Source

putStrLn :: (Encoding e, ?enc :: e) => String -> IO () Source

hPutStr :: (Encoding e, ?enc :: e) => Handle -> String -> IO () Source

Like the normal hPutStr, but encodes the output using an encoding.

hPutStrLn :: (Encoding e, ?enc :: e) => Handle -> String -> IO () Source

hGetContents :: (Encoding e, ?enc :: e) => Handle -> IO String Source

Like the normal hGetContents, but decodes the input using an encoding.

readFile :: (Encoding e, ?enc :: e) => FilePath -> IO String Source

writeFile :: (Encoding e, ?enc :: e) => FilePath -> String -> IO () Source

appendFile :: (Encoding e, ?enc :: e) => FilePath -> String -> IO () Source

getChar :: (Encoding e, ?enc :: e) => IO Char Source

hGetChar :: (Encoding e, ?enc :: e) => Handle -> IO Char Source

getLine :: (Encoding e, ?enc :: e) => IO String Source

hGetLine :: (Encoding e, ?enc :: e) => Handle -> IO String Source

putChar :: (Encoding e, ?enc :: e) => Char -> IO () Source

hPutChar :: (Encoding e, ?enc :: e) => Handle -> Char -> IO () Source

interact :: (Encoding e, ?enc :: e) => (String -> String) -> IO () Source

print :: (Encoding e, Show a, ?enc :: e) => a -> IO () Source

hPrint :: (Encoding e, Show a, ?enc :: e) => Handle -> a -> IO () Source