diff options
author | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2008-08-14 01:32:54 +0000 |
---|---|---|
committer | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2008-08-14 01:32:54 +0000 |
commit | d00da316227c26bad857998d0398a23917ee0a7b (patch) | |
tree | ef4ae5ec42114e9a8e94cb83f50368c6af849e33 /Text | |
parent | 8388427d230e853466298cfae7abf0ac0af50269 (diff) | |
download | pandoc-d00da316227c26bad857998d0398a23917ee0a7b.tar.gz |
Simplified and improved UTF8 handling:
+ Removed utf8-string cabal configuration flag.
+ Instead, we just include System.IO.UTF8 and Codec.Binary.UTF8.String
from utf8-string package in the source tree, avoiding a dependency
on utf8-string and avoiding crufty custom UTF8 code. (The old
Text.Pandoc.UTF8 had problems with the getContents function.)
+ Removed lots of CPP directives that are no longer needed.
+ In Setup.hs, use '-i..' in running RunTests.hs, so the local UTF8
code will be found.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1411 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'Text')
-rw-r--r-- | Text/Pandoc/ODT.hs | 6 | ||||
-rw-r--r-- | Text/Pandoc/PDF.hs | 5 | ||||
-rw-r--r-- | Text/Pandoc/Shared.hs | 4 | ||||
-rw-r--r-- | Text/Pandoc/TH.hs | 5 | ||||
-rw-r--r-- | Text/Pandoc/UTF8.hs | 76 |
5 files changed, 1 insertions, 95 deletions
diff --git a/Text/Pandoc/ODT.hs b/Text/Pandoc/ODT.hs index 763625e24..8c3b1b45f 100644 --- a/Text/Pandoc/ODT.hs +++ b/Text/Pandoc/ODT.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TemplateHaskell, CPP #-} +{-# LANGUAGE TemplateHaskell #-} {- Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu> @@ -44,11 +44,7 @@ import qualified Data.ByteString as B ( writeFile, pack ) import Data.ByteString.Internal ( c2w ) import Prelude hiding ( writeFile, readFile ) import System.IO ( stderr ) -#ifdef _UTF8STRING import System.IO.UTF8 -#else -import Text.Pandoc.UTF8 -#endif -- | Produce an ODT file from OpenDocument XML. saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced. diff --git a/Text/Pandoc/PDF.hs b/Text/Pandoc/PDF.hs index 4257e4712..1e2d5e9b5 100644 --- a/Text/Pandoc/PDF.hs +++ b/Text/Pandoc/PDF.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {- Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu> @@ -38,11 +37,7 @@ import System.Environment ( getEnvironment ) import Text.Pandoc.Shared ( withTempDir ) import Prelude hiding ( writeFile, readFile, putStrLn ) import System.IO ( stderr, openFile, IOMode (..), hClose ) -#ifdef _UTF8STRING import System.IO.UTF8 -#else -import Text.Pandoc.UTF8 -#endif -- | Produce an PDF file from LaTeX. saveLaTeXAsPDF :: FilePath -- ^ Pathname of PDF file to be produced. diff --git a/Text/Pandoc/Shared.hs b/Text/Pandoc/Shared.hs index 38c1cf6b4..2c53ffa7a 100644 --- a/Text/Pandoc/Shared.hs +++ b/Text/Pandoc/Shared.hs @@ -118,11 +118,7 @@ import System.FilePath ( (</>), (<.>) ) import System.IO.Error ( catch, ioError, isAlreadyExistsError ) import System.Directory import Prelude hiding ( putStrLn, writeFile, readFile, getContents ) -#ifdef _UTF8STRING import System.IO.UTF8 -#else -import Text.Pandoc.UTF8 -#endif -- -- List processing diff --git a/Text/Pandoc/TH.hs b/Text/Pandoc/TH.hs index 376dfa00d..dfd6be28b 100644 --- a/Text/Pandoc/TH.hs +++ b/Text/Pandoc/TH.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu> @@ -39,11 +38,7 @@ import Language.Haskell.TH.Syntax (Lift (..)) import qualified Data.ByteString as B import Data.ByteString.Internal ( w2c ) import Prelude hiding ( readFile ) -#ifdef _UTF8STRING import System.IO.UTF8 -#else -import Text.Pandoc.UTF8 -#endif -- | Insert contents of text file into a template. contentsOf :: FilePath -> ExpQ diff --git a/Text/Pandoc/UTF8.hs b/Text/Pandoc/UTF8.hs deleted file mode 100644 index f8d041db7..000000000 --- a/Text/Pandoc/UTF8.hs +++ /dev/null @@ -1,76 +0,0 @@ --- | Functions for IO using UTF-8 encoding. --- --- The basic encoding and decoding functions are taken from --- <http://www.cse.ogi.edu/~hallgren/Talks/LHiH/base/lib/UTF8.hs>. --- (c) 2003, OGI School of Science & Engineering, Oregon Health and --- Science University. --- --- From the Char module supplied with HBC. --- Modified by Martin Norbaeck to pass illegal UTF-8 sequences unchanged. --- Modified by John MacFarlane to use [Word8] and export IO functions. - -module Text.Pandoc.UTF8 ( - putStrLn - , putStr - , hPutStrLn - , hPutStr - , getContents - , readFile - , writeFile - ) where -import Data.Word -import System.IO ( Handle ) -import qualified Data.ByteString.Lazy as BS -import Prelude hiding ( putStrLn, putStr, getContents, readFile, writeFile ) - -putStrLn :: String -> IO () -putStrLn = BS.putStrLn . BS.pack . toUTF8 - -putStr :: String -> IO () -putStr = BS.putStr . BS.pack . toUTF8 - -hPutStrLn :: Handle -> String -> IO () -hPutStrLn h = BS.hPut h . BS.pack . toUTF8 . (++ "\n") - -hPutStr :: Handle -> String -> IO () -hPutStr h = BS.hPut h . BS.pack . toUTF8 - -readFile :: FilePath -> IO String -readFile p = BS.readFile p >>= return . fromUTF8 . BS.unpack - -writeFile :: FilePath -> String -> IO () -writeFile p = BS.writeFile p . BS.pack . toUTF8 - -getContents :: IO String -getContents = BS.getContents >>= return . fromUTF8 . BS.unpack - --- | Take a list of bytes in UTF-8 encoding and decode it into a Unicode string. -fromUTF8 :: [Word8] -> String -fromUTF8 [] = "" -fromUTF8 (0xef : 0xbb : 0xbf :cs) = fromUTF8 cs -- skip BOM (byte order marker) -fromUTF8 (c:c':cs) | 0xc0 <= c && c <= 0xdf && - 0x80 <= c' && c' <= 0xbf = - toEnum ((fromEnum c `mod` 0x20) * 0x40 + fromEnum c' `mod` 0x40) : fromUTF8 cs -fromUTF8 (c:c':c'':cs) | 0xe0 <= c && c <= 0xef && - 0x80 <= c' && c' <= 0xbf && - 0x80 <= c'' && c'' <= 0xbf = - toEnum ((fromEnum c `mod` 0x10 * 0x1000) + (fromEnum c' `mod` 0x40) * 0x40 + fromEnum c'' `mod` 0x40) : fromUTF8 cs -fromUTF8 (c:cs) = toEnum (fromEnum c) : fromUTF8 cs - --- | Take a Unicode string and encode it as a list of bytes in UTF-8 encoding. -toUTF8 :: String -> [Word8] -toUTF8 "" = [] -toUTF8 (c:cs) = - if c > '\x0000' && c < '\x0080' then - toEnum (fromEnum c) : toUTF8 cs - else if c < toEnum 0x0800 then - let i = fromEnum c - in toEnum (0xc0 + i `div` 0x40) : - toEnum (0x80 + i `mod` 0x40) : - toUTF8 cs - else - let i = fromEnum c - in toEnum (0xe0 + i `div` 0x1000) : - toEnum (0x80 + (i `mod` 0x1000) `div` 0x40) : - toEnum (0x80 + i `mod` 0x40) : - toUTF8 cs |