2010-05-06 20:27:10 -07:00
|
|
|
{-
|
|
|
|
Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu>
|
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
|
|
|
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.UTF8
|
|
|
|
Copyright : Copyright (C) 2010 John MacFarlane
|
2012-07-26 22:32:53 -07:00
|
|
|
License : GNU GPL, version 2 or above
|
2010-05-06 20:27:10 -07:00
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
2011-01-30 16:01:31 -08:00
|
|
|
UTF-8 aware string IO functions that will work with GHC 6.10, 6.12, or 7.
|
2010-05-06 20:27:10 -07:00
|
|
|
-}
|
|
|
|
module Text.Pandoc.UTF8 ( readFile
|
|
|
|
, writeFile
|
|
|
|
, getContents
|
|
|
|
, putStr
|
|
|
|
, putStrLn
|
|
|
|
, hPutStr
|
|
|
|
, hPutStrLn
|
2011-01-30 16:01:31 -08:00
|
|
|
, hGetContents
|
2012-09-23 10:43:03 -07:00
|
|
|
, encodePath
|
2010-05-06 20:27:10 -07:00
|
|
|
)
|
|
|
|
|
|
|
|
where
|
2011-01-30 16:01:31 -08:00
|
|
|
|
2012-06-25 14:27:22 -07:00
|
|
|
#if MIN_VERSION_base(4,4,0)
|
2012-06-22 21:24:02 +02:00
|
|
|
#else
|
|
|
|
import Codec.Binary.UTF8.String (encodeString)
|
|
|
|
#endif
|
|
|
|
|
2011-01-30 17:01:50 -08:00
|
|
|
#if MIN_VERSION_base(4,2,0)
|
2011-01-30 16:01:31 -08:00
|
|
|
|
|
|
|
import System.IO hiding (readFile, writeFile, getContents,
|
|
|
|
putStr, putStrLn, hPutStr, hPutStrLn, hGetContents)
|
|
|
|
import Prelude hiding (readFile, writeFile, getContents, putStr, putStrLn )
|
|
|
|
import qualified System.IO as IO
|
|
|
|
|
|
|
|
readFile :: FilePath -> IO String
|
|
|
|
readFile f = do
|
2012-06-22 21:24:02 +02:00
|
|
|
h <- openFile (encodePath f) ReadMode
|
2011-01-30 16:01:31 -08:00
|
|
|
hGetContents h
|
|
|
|
|
|
|
|
writeFile :: FilePath -> String -> IO ()
|
2012-06-22 21:24:02 +02:00
|
|
|
writeFile f s = withFile (encodePath f) WriteMode $ \h -> hPutStr h s
|
2011-01-30 16:01:31 -08:00
|
|
|
|
|
|
|
getContents :: IO String
|
|
|
|
getContents = hGetContents stdin
|
|
|
|
|
|
|
|
putStr :: String -> IO ()
|
|
|
|
putStr s = hPutStr stdout s
|
|
|
|
|
|
|
|
putStrLn :: String -> IO ()
|
|
|
|
putStrLn s = hPutStrLn stdout s
|
|
|
|
|
|
|
|
hPutStr :: Handle -> String -> IO ()
|
|
|
|
hPutStr h s = hSetEncoding h utf8 >> IO.hPutStr h s
|
|
|
|
|
|
|
|
hPutStrLn :: Handle -> String -> IO ()
|
|
|
|
hPutStrLn h s = hSetEncoding h utf8 >> IO.hPutStrLn h s
|
|
|
|
|
|
|
|
hGetContents :: Handle -> IO String
|
|
|
|
hGetContents h = hSetEncoding h utf8_bom >> IO.hGetContents h
|
|
|
|
|
|
|
|
#else
|
|
|
|
|
2010-07-21 15:14:20 -07:00
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import Data.ByteString.UTF8 (toString, fromString)
|
2010-05-06 20:27:10 -07:00
|
|
|
import Prelude hiding (readFile, writeFile, getContents, putStr, putStrLn)
|
|
|
|
import System.IO (Handle)
|
|
|
|
import Control.Monad (liftM)
|
|
|
|
|
2011-01-30 16:01:31 -08:00
|
|
|
|
2010-05-06 23:04:44 -07:00
|
|
|
bom :: B.ByteString
|
|
|
|
bom = B.pack [0xEF, 0xBB, 0xBF]
|
|
|
|
|
|
|
|
stripBOM :: B.ByteString -> B.ByteString
|
|
|
|
stripBOM s | bom `B.isPrefixOf` s = B.drop 3 s
|
|
|
|
stripBOM s = s
|
|
|
|
|
2010-05-06 20:27:10 -07:00
|
|
|
readFile :: FilePath -> IO String
|
2012-06-22 21:24:02 +02:00
|
|
|
readFile = liftM (toString . stripBOM) . B.readFile . encodePath
|
2010-05-06 20:27:10 -07:00
|
|
|
|
|
|
|
writeFile :: FilePath -> String -> IO ()
|
2012-06-22 21:24:02 +02:00
|
|
|
writeFile f = B.writeFile (encodePath f) . fromString
|
2010-05-06 20:27:10 -07:00
|
|
|
|
|
|
|
getContents :: IO String
|
2010-05-06 23:04:44 -07:00
|
|
|
getContents = liftM (toString . stripBOM) B.getContents
|
2010-05-06 20:27:10 -07:00
|
|
|
|
2011-01-30 16:01:31 -08:00
|
|
|
hGetContents :: Handle -> IO String
|
|
|
|
hGetContents h = liftM (toString . stripBOM) (B.hGetContents h)
|
|
|
|
|
2010-05-06 20:27:10 -07:00
|
|
|
putStr :: String -> IO ()
|
|
|
|
putStr = B.putStr . fromString
|
|
|
|
|
|
|
|
putStrLn :: String -> IO ()
|
|
|
|
putStrLn = B.putStrLn . fromString
|
|
|
|
|
|
|
|
hPutStr :: Handle -> String -> IO ()
|
|
|
|
hPutStr h = B.hPutStr h . fromString
|
|
|
|
|
|
|
|
hPutStrLn :: Handle -> String -> IO ()
|
|
|
|
hPutStrLn h s = hPutStr h (s ++ "\n")
|
2011-01-30 16:01:31 -08:00
|
|
|
|
|
|
|
#endif
|
2012-06-22 21:24:02 +02:00
|
|
|
|
|
|
|
encodePath :: FilePath -> FilePath
|
2012-06-25 14:27:22 -07:00
|
|
|
#if MIN_VERSION_base(4,4,0)
|
2012-06-22 21:24:02 +02:00
|
|
|
encodePath = id
|
|
|
|
#else
|
|
|
|
encodePath = encodeString
|
|
|
|
#endif
|