diff --git a/System/IO/UTF8.hs b/System/IO/UTF8.hs index d0af4c38e84de73b87c863ce390548002b2923a9..81d6ab824bbf53520f5a5b26d467836eaf8ab153 100644 --- a/System/IO/UTF8.hs +++ b/System/IO/UTF8.hs @@ -17,6 +17,8 @@ module System.IO.UTF8 ( , putStrLn , getLine , readLn + , openBinaryFile + , withBinaryFile , readFile , writeFile , appendFile @@ -28,11 +30,10 @@ module System.IO.UTF8 ( ) where import Control.Monad (liftM) -import Data.Char (ord, chr) import Data.Word (Word8) -import Prelude (String, ($), (=<<), (>>=), (.), map, toEnum, fromEnum, Read, +import Prelude (String, (=<<), (.), map, Enum(toEnum, fromEnum), Read, Show(..)) -import System.IO (Handle, IO, FilePath) +import System.IO (Handle, IO, FilePath, IOMode(AppendMode, ReadMode, WriteMode)) import qualified System.IO as IO import Codec.Binary.UTF8.String (encode, decode) @@ -48,11 +49,11 @@ decodeString xs = decode (stringToBytes xs) -- | Convert a list of bytes to a String bytesToString :: [Word8] -> String -bytesToString xs = map (chr . fromEnum) xs +bytesToString xs = map (toEnum . fromEnum) xs -- | String to list of bytes. stringToBytes :: String -> [Word8] -stringToBytes xs = map (toEnum . ord) xs +stringToBytes xs = map (toEnum . fromEnum) xs -- | The 'print' function outputs a value of any printable type to the -- standard output device. This function differs from the @@ -77,28 +78,31 @@ getLine = liftM decodeString IO.getLine readLn :: Read a => IO a readLn = IO.readIO =<< getLine +openBinaryFile :: FilePath -> IOMode -> IO Handle +openBinaryFile n m = IO.openBinaryFile (encodeString n) m + +withBinaryFile :: FilePath -> IOMode -> (Handle -> IO a) -> IO a +withBinaryFile n m f = IO.withBinaryFile (encodeString n) m f + -- | The 'readFile' function reads a file and -- returns the contents of the file as a UTF8 string. -- The file is read lazily, on demand, as with 'getContents'. readFile :: FilePath -> IO String -readFile n = liftM decodeString (IO.openBinaryFile n IO.ReadMode >>= - IO.hGetContents) +readFile n = hGetContents =<< openBinaryFile n ReadMode -- | The computation 'writeFile' @file str@ function writes the UTF8 string @str@, -- to the file @file@. writeFile :: FilePath -> String -> IO () -writeFile n c = IO.withBinaryFile n IO.WriteMode $ \ h -> - IO.hPutStr h $ encodeString c +writeFile n s = withBinaryFile n WriteMode (\ h -> hPutStr h s) -- | The computation 'appendFile' @file str@ function appends the UTF8 string @str@, -- to the file @file@. appendFile :: FilePath -> String -> IO () -appendFile n c = IO.withBinaryFile n IO.AppendMode $ \h -> - IO.hPutStr h $ encodeString c +appendFile n s = withBinaryFile n AppendMode (\ h -> hPutStr h s) -- | Read a UTF8 line from a Handle hGetLine :: Handle -> IO String -hGetLine h = liftM decodeString $ IO.hGetLine h +hGetLine h = liftM decodeString (IO.hGetLine h) -- | Lazily read a UTF8 string from a Handle hGetContents :: Handle -> IO String diff --git a/utf8-string.cabal b/utf8-string.cabal index d3398bd3237bf9d9cbc4e3d3289c8f08c56da7a9..ceb9dbf81b2e55a164f27ecad586ba24712853f2 100644 --- a/utf8-string.cabal +++ b/utf8-string.cabal @@ -1,5 +1,5 @@ Name: utf8-string -Version: 0.3.1.1 +Version: 0.3.2 Author: Eric Mertens Maintainer: emertens@galois.com License: BSD3