From 30375bb84737bd9536a73fc1929c15c50a80a655 Mon Sep 17 00:00:00 2001 From: fiddlosopher Date: Fri, 13 Jul 2007 06:34:33 +0000 Subject: Changed encodeUTF8 to toUTF8, decodeUTF8 to fromUTF8, for clarity. git-svn-id: https://pandoc.googlecode.com/svn/trunk@692 788f1e2b-df1e-0410-8736-df70ead52e1b --- src/Main.hs | 12 +++++------- src/Text/Pandoc.hs | 4 ++-- src/Text/Pandoc/UTF8.hs | 32 ++++++++++++++++---------------- 3 files changed, 23 insertions(+), 25 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index d55e6ad0f..49cc33040 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -30,8 +30,8 @@ writers. -} module Main where import Text.Pandoc -import Text.Pandoc.UTF8 ( encodeUTF8, decodeUTF8 ) -import Text.Pandoc.ASCIIMathML ( asciiMathMLScript ) +import Text.Pandoc.UTF8 +import Text.Pandoc.ASCIIMathML import Text.Pandoc.Shared ( joinWithSep, tabsToSpaces ) import Text.Regex ( mkRegex, matchRegex ) import System.Environment ( getArgs, getProgName, getEnvironment ) @@ -439,9 +439,7 @@ main = do Nothing -> stateColumns defaultParserState let tabFilter = if preserveTabs then id else (tabsToSpaces tabStop) - let addBlank str = str let removeCRs str = filter (/= '\r') str -- remove DOS-style line endings - let filter = tabFilter . addBlank . removeCRs let startParserState = defaultParserState { stateParseRaw = parseRaw, stateTabStop = tabStop, @@ -475,10 +473,10 @@ main = do writerStrictMarkdown = strict, writerReferenceLinks = referenceLinks } - (readSources sources) >>= (hPutStr output . encodeUTF8 . + (readSources sources) >>= (hPutStr output . toUTF8 . (writer writerOptions) . - (reader startParserState) . filter . - decodeUTF8 . (joinWithSep "\n")) >> + (reader startParserState) . tabFilter . + removeCRs . fromUTF8 . (joinWithSep "\n")) >> hClose output where diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 2be7d9642..ad24eef4d 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -38,9 +38,9 @@ inline links: > import Text.Pandoc > > markdownToRST :: String -> String -> markdownToRST = encodeUTF8 . +> markdownToRST = toUTF8 . > (writeRST defaultWriterOptions {writerReferenceLinks = True}) . -> (readMarkdown defaultParserState) . decodeUTF8 +> (readMarkdown defaultParserState) . fromUTF8 > > main = interact markdownToRST diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs index 927157ba5..be26f4993 100644 --- a/src/Text/Pandoc/UTF8.hs +++ b/src/Text/Pandoc/UTF8.hs @@ -7,38 +7,38 @@ -- Modified by Martin Norbaeck -- to pass illegal UTF-8 sequences through unchanged. module Text.Pandoc.UTF8 ( - decodeUTF8, - encodeUTF8 + fromUTF8, + toUTF8 ) where -- From the Char module supplied with HBC. -- | Take a UTF-8 string and decode it into a Unicode string. -decodeUTF8 :: String -> String -decodeUTF8 "" = "" -decodeUTF8 (c:c':cs) | '\xc0' <= c && c <= '\xdf' && - '\x80' <= c' && c' <= '\xbf' = - toEnum ((fromEnum c `mod` 0x20) * 0x40 + fromEnum c' `mod` 0x40) : decodeUTF8 cs -decodeUTF8 (c:c':c'':cs) | '\xe0' <= c && c <= '\xef' && +fromUTF8 :: String -> String +fromUTF8 "" = "" +fromUTF8 (c:c':cs) | '\xc0' <= c && c <= '\xdf' && + '\x80' <= c' && c' <= '\xbf' = + toEnum ((fromEnum c `mod` 0x20) * 0x40 + fromEnum c' `mod` 0x40) : fromUTF8 cs +fromUTF8 (c:c':c'':cs) | '\xe0' <= c && c <= '\xef' && '\x80' <= c' && c' <= '\xbf' && '\x80' <= c'' && c'' <= '\xbf' = - toEnum ((fromEnum c `mod` 0x10 * 0x1000) + (fromEnum c' `mod` 0x40) * 0x40 + fromEnum c'' `mod` 0x40) : decodeUTF8 cs -decodeUTF8 (c:cs) = c : decodeUTF8 cs + toEnum ((fromEnum c `mod` 0x10 * 0x1000) + (fromEnum c' `mod` 0x40) * 0x40 + fromEnum c'' `mod` 0x40) : fromUTF8 cs +fromUTF8 (c:cs) = c : fromUTF8 cs -- | Take a Unicode string and encode it as a UTF-8 string. -encodeUTF8 :: String -> String -encodeUTF8 "" = "" -encodeUTF8 (c:cs) = +toUTF8 :: String -> String +toUTF8 "" = "" +toUTF8 (c:cs) = if c > '\x0000' && c < '\x0080' then - c : encodeUTF8 cs + c : toUTF8 cs else if c < toEnum 0x0800 then let i = fromEnum c in toEnum (0xc0 + i `div` 0x40) : toEnum (0x80 + i `mod` 0x40) : - encodeUTF8 cs + 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) : - encodeUTF8 cs + toUTF8 cs -- cgit v1.2.3