diff --git a/CHANGELOG.markdown b/CHANGELOG.markdown index 6c0340e61b9a5ec8086a80b58123dae737139a8c..536c6d602c4f3f438ae93bb870a64ac1fe58afce 100644 --- a/CHANGELOG.markdown +++ b/CHANGELOG.markdown @@ -1,3 +1,7 @@ +1 +----- +* Remove out all the old utf8 IO support. GHC supports utf8 now. + 0.3.8 ----- * Performance tweaks diff --git a/System/Environment/UTF8.hs b/System/Environment/UTF8.hs deleted file mode 100644 index a0970550faeefc4be5d74125aff867a20bc02172..0000000000000000000000000000000000000000 --- a/System/Environment/UTF8.hs +++ /dev/null @@ -1,41 +0,0 @@ -{-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Trustworthy #-} -#endif --- --- | --- Module : System.Environment.UTF8 --- Copyright : (c) Eric Mertens 2009 --- License : BSD3-style (see LICENSE) --- --- Maintainer: emertens@galois.com --- Stability : experimental --- Portability : portable --- --- Support for UTF-8 based environment manipulation --- -module System.Environment.UTF8 - (getArgs, getProgName, getEnv, withArgs, withProgName, getEnvironment) - where - -import Codec.Binary.UTF8.String (decodeString) -import qualified System.Environment as Sys - -getArgs :: IO [String] -getArgs = map decodeString `fmap` Sys.getArgs - -getProgName :: IO String -getProgName = decodeString `fmap` Sys.getProgName - -getEnv :: String -> IO String -getEnv x = decodeString `fmap` Sys.getEnv x - -withArgs :: [String] -> IO a -> IO a -withArgs = Sys.withArgs - -withProgName :: String -> IO a -> IO a -withProgName = Sys.withProgName - -getEnvironment :: IO [(String,String)] -getEnvironment = map f `fmap` Sys.getEnvironment - where f (a,b) = (decodeString a, decodeString b) diff --git a/System/IO/UTF8.hs b/System/IO/UTF8.hs deleted file mode 100644 index a6b5818fef553a3f33f8399213750e9f9977d7c8..0000000000000000000000000000000000000000 --- a/System/IO/UTF8.hs +++ /dev/null @@ -1,130 +0,0 @@ -{-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Trustworthy #-} -#endif ------------------------------------------------------------------------------ --- | --- Module : System.IO.UTF8 --- Copyright : (c) Eric Mertens 2007 --- License : BSD3-style (see LICENSE) --- --- Maintainer: emertens@galois.com --- Stability : experimental --- Portability : portable --- --- String IO preserving UTF8 encoding. --- - -module System.IO.UTF8 ( - print - , putStr - , putStrLn - , getLine - , readLn - , openBinaryFile - , withBinaryFile - , readFile - , writeFile - , appendFile - , interact - , getContents - , hGetLine - , hGetContents - , hPutStr - , hPutStrLn - ) where - -import Control.Monad (liftM) -import Data.Word (Word8) -import Prelude (String, (=<<), (.), map, Enum(toEnum, fromEnum), Read, - Show(..)) -import System.IO (Handle, IO, FilePath, IOMode(AppendMode, ReadMode, WriteMode)) -import qualified System.IO as IO -import Control.Exception (bracket) - -import Codec.Binary.UTF8.String (encode, decode) - - --- | Encode a string in UTF8 form. -encodeString :: String -> String -encodeString xs = bytesToString (encode xs) - --- | Decode a string from UTF8 -decodeString :: String -> String -decodeString xs = decode (stringToBytes xs) - --- | Convert a list of bytes to a String -bytesToString :: [Word8] -> String -bytesToString xs = map (toEnum . fromEnum) xs - --- | String to list of bytes. -stringToBytes :: String -> [Word8] -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 --- System.IO.print in that it preserves any UTF8 encoding of the shown value. --- -print :: Show a => a -> IO () -print x = putStrLn (show x) - --- | Write a UTF8 string to the standard output device -putStr :: String -> IO () -putStr x = IO.putStr (encodeString x) - --- | The same as 'putStr', but adds a newline character. -putStrLn :: String -> IO () -putStrLn x = IO.putStrLn (encodeString x) - --- | Read a UTF8 line from the standard input device -getLine :: IO String -getLine = liftM decodeString IO.getLine - --- | The 'readLn' function combines 'getLine' and 'readIO', preserving UTF8 -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 = bracket (openBinaryFile n m) IO.hClose 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 = 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 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 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) - --- | Lazily read a UTF8 string from a Handle -hGetContents :: Handle -> IO String -hGetContents h = liftM decodeString (IO.hGetContents h) - --- | Write a UTF8 string to a Handle. -hPutStr :: Handle -> String -> IO () -hPutStr h s = IO.hPutStr h (encodeString s) - --- | Write a UTF8 string to a Handle, appending a newline. -hPutStrLn :: Handle -> String -> IO () -hPutStrLn h s = IO.hPutStrLn h (encodeString s) - --- | Lazily read stdin as a UTF8 string. -getContents :: IO String -getContents = liftM decodeString IO.getContents - -interact :: (String -> String) -> IO () -interact f = IO.interact (encodeString . f . decodeString) diff --git a/utf8-string.cabal b/utf8-string.cabal index 221b004ecbef6f5b1aa7c80fcd553936b077352e..a0b6d7e38a35fde2f341326dbcdfaf3877af0b26 100644 --- a/utf8-string.cabal +++ b/utf8-string.cabal @@ -1,12 +1,12 @@ Name: utf8-string -Version: 0.3.8 +Version: 1 Author: Eric Mertens Maintainer: emertens@galois.com License: BSD3 License-file: LICENSE Homepage: http://github.com/glguy/utf8-string/ Synopsis: Support for reading and writing UTF8 Strings -Description: A UTF8 layer for IO and Strings. The utf8-string +Description: A UTF8 layer for Strings. The utf8-string package provides operations for encoding UTF8 strings to Word8 lists and back, and for reading and writing UTF8 without truncation. @@ -15,24 +15,14 @@ Build-type: Simple cabal-version: >= 1.2 Extra-Source-Files: CHANGELOG.markdown - -flag bytestring-in-base - default: False - library Ghc-options: -W -O2 - if flag(bytestring-in-base) - build-depends: base >= 2.0 && < 2.2 - cpp-options: -DBYTESTRING_IN_BASE - else - build-depends: base < 2.0 || >= 3, bytestring >= 0.9 + build-depends: base >= 4.3, bytestring >= 0.9 Extensions: CPP Exposed-modules: Codec.Binary.UTF8.String Codec.Binary.UTF8.Generic - System.IO.UTF8 - System.Environment.UTF8 Data.String.UTF8 Data.ByteString.UTF8 Data.ByteString.Lazy.UTF8