diff options
author | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2008-08-08 00:11:58 +0000 |
---|---|---|
committer | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2008-08-08 00:11:58 +0000 |
commit | 80715bd126925c73cc2cb79e18c641506537566a (patch) | |
tree | 77211df8cb7c1fd0ebdfec670a347ae58c8cec77 /Text/Pandoc | |
parent | 05b366a0b217a6cae33bd1d36b66faa211860ba8 (diff) | |
download | pandoc-80715bd126925c73cc2cb79e18c641506537566a.tar.gz |
Added Text.Pandoc.UTF8 as a backup for when utf8-string is not present.
+ Added Text.Pandoc.UTF8
+ Changed flag name from utf8 to utf8-string
+ Changed CPP MACRO from _UTF8 to _UTF8STRING
+ Import IO functions from Text.Pandoc.UTF8 when utf8-string not available.
+ Removed utf8-string dependency from debian/control.
+ Removed pandoc.cabal.ghc66; we no longer support GHC 6.6
+ Modified INSTALL instructions
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1383 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'Text/Pandoc')
-rw-r--r-- | Text/Pandoc/ODT.hs | 6 | ||||
-rw-r--r-- | Text/Pandoc/Shared.hs | 6 | ||||
-rw-r--r-- | Text/Pandoc/TH.hs | 4 | ||||
-rw-r--r-- | Text/Pandoc/UTF8.hs | 76 |
4 files changed, 84 insertions, 8 deletions
diff --git a/Text/Pandoc/ODT.hs b/Text/Pandoc/ODT.hs index b0bfc6693..5b900bf03 100644 --- a/Text/Pandoc/ODT.hs +++ b/Text/Pandoc/ODT.hs @@ -43,11 +43,11 @@ import Network.URI ( isURI ) import qualified Data.ByteString as B ( writeFile, pack ) import Data.ByteString.Internal ( c2w ) import Prelude hiding ( writeFile, readFile ) -#ifdef _UTF8 -import System.IO.UTF8 import System.IO ( stderr ) +#ifdef _UTF8STRING +import System.IO.UTF8 #else -import System.IO +import Text.Pandoc.UTF8 #endif -- | Produce an ODT file from OpenDocument XML. diff --git a/Text/Pandoc/Shared.hs b/Text/Pandoc/Shared.hs index bc0791d77..6f37f633b 100644 --- a/Text/Pandoc/Shared.hs +++ b/Text/Pandoc/Shared.hs @@ -116,11 +116,11 @@ import Network.URI ( parseURI, URI (..), isAllowedInURI ) import System.FilePath ( (</>), (<.>) ) import System.IO.Error ( catch, ioError, isAlreadyExistsError ) import System.Directory -import Prelude hiding ( putStrLn ) -#ifdef _UTF8 +import Prelude hiding ( putStrLn, writeFile, readFile, getContents ) +#ifdef _UTF8STRING import System.IO.UTF8 #else -import System.IO +import Text.Pandoc.UTF8 #endif -- diff --git a/Text/Pandoc/TH.hs b/Text/Pandoc/TH.hs index 30f5c86e4..376dfa00d 100644 --- a/Text/Pandoc/TH.hs +++ b/Text/Pandoc/TH.hs @@ -39,10 +39,10 @@ import Language.Haskell.TH.Syntax (Lift (..)) import qualified Data.ByteString as B import Data.ByteString.Internal ( w2c ) import Prelude hiding ( readFile ) -#ifdef _UTF8 +#ifdef _UTF8STRING import System.IO.UTF8 #else -import System.IO +import Text.Pandoc.UTF8 #endif -- | Insert contents of text file into a template. diff --git a/Text/Pandoc/UTF8.hs b/Text/Pandoc/UTF8.hs new file mode 100644 index 000000000..f8d041db7 --- /dev/null +++ b/Text/Pandoc/UTF8.hs @@ -0,0 +1,76 @@ +-- | 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 |