Change 'HtmlEntities' module to 'Entities'. Adjusted calling

code accordingly.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@395 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2007-01-02 00:40:12 +00:00
parent 4e5745134a
commit d4454536f0
7 changed files with 22 additions and 21 deletions

View file

@ -17,7 +17,7 @@ Extra-Source-Files: README COPYRIGHT man/man1/pandoc.1
Exposed-Modules: Text.ParserCombinators.Pandoc,
Text.Pandoc.ASCIIMathML,
Text.Pandoc.Definition,
Text.Pandoc.HtmlEntities,
Text.Pandoc.Entities,
Text.Pandoc.Shared,
Text.Pandoc.UTF8,
Text.Pandoc.Writers.DefaultHeaders,

View file

@ -336,6 +336,7 @@ defaultWriterName x =
Just ["markdown"] -> "markdown"
Just ["db"] -> "docbook"
Just ["xml"] -> "docbook"
Just ["sgml"] -> "docbook"
Just _ -> "html"
main = do

View file

@ -17,7 +17,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
Module : Text.Pandoc.HtmlEntities
Module : Text.Pandoc.Entities
Copyright : Copyright (C) 2006 John MacFarlane
License : GNU GPL, version 2 or above
@ -25,12 +25,12 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Stability : alpha
Portability : portable
Functions for encoding unicode characters as HTML entity references,
Functions for encoding unicode characters as entity references,
and vice versa.
-}
module Text.Pandoc.HtmlEntities (
htmlEntityToChar,
charToHtmlEntity,
module Text.Pandoc.Entities (
entityToChar,
charToEntity,
decodeEntities,
encodeEntities
) where
@ -50,7 +50,7 @@ decodeEntities str =
Nothing -> str
Just (before, match, rest, _) -> before ++ replacement ++
(decodeEntities rest)
where replacement = case (htmlEntityToChar match) of
where replacement = case (entityToChar match) of
Just ch -> [ch]
Nothing -> match
@ -60,29 +60,29 @@ encodeEntities :: String -> String
encodeEntities [] = []
encodeEntities (c:cs) = if ord c < 127
then c:(encodeEntities cs)
else (charToHtmlEntity c) ++ (encodeEntities cs)
else (charToEntity c) ++ (encodeEntities cs)
-- | If the string is a valid entity reference, returns @Just@ the character,
-- otherwise @Nothing@.
htmlEntityToChar :: String -> Maybe Char
htmlEntityToChar entity =
case (lookup entity htmlEntityTable) of
entityToChar :: String -> Maybe Char
entityToChar entity =
case (lookup entity entityTable) of
Just ch -> Just ch
Nothing -> case (matchRegexAll decimalCodedEntity entity) of
Just (_, _, _, [sub]) -> Just (chr (read sub))
Nothing -> Nothing
-- | Returns a string containing an entity reference for the character.
charToHtmlEntity :: Char -> String
charToHtmlEntity char =
charToEntity :: Char -> String
charToEntity char =
let matches = filter (\(entity, character) -> (character == char))
htmlEntityTable in
entityTable in
if (length matches) == 0
then "&#" ++ show (ord char) ++ ";"
else fst (head matches)
htmlEntityTable :: [(String, Char)]
htmlEntityTable = [
entityTable :: [(String, Char)]
entityTable = [
("&quot;", chr 34),
("&amp;", chr 38),
("&lt;", chr 60),

View file

@ -45,7 +45,7 @@ import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Pandoc
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.HtmlEntities ( decodeEntities, htmlEntityToChar )
import Text.Pandoc.Entities ( decodeEntities, entityToChar )
import Maybe ( fromMaybe )
import Char ( toUpper, toLower )
@ -397,7 +397,7 @@ entity = try (do
num <- many1 digit
return ("#" ++ num)))]
char ';'
return (Str [fromMaybe '?' (htmlEntityToChar ("&" ++ body ++ ";"))]))
return (Str [fromMaybe '?' (entityToChar ("&" ++ body ++ ";"))]))
code = try (do
htmlTag "code"

View file

@ -41,7 +41,7 @@ import Text.Pandoc.Readers.HTML ( rawHtmlBlock,
anyHtmlTag, anyHtmlEndTag,
htmlEndTag, extractTagType,
htmlBlockElement )
import Text.Pandoc.HtmlEntities ( decodeEntities )
import Text.Pandoc.Entities ( decodeEntities )
import Text.Regex ( matchRegex, mkRegex )
import Text.ParserCombinators.Parsec

View file

@ -66,7 +66,7 @@ module Text.Pandoc.Shared (
) where
import Text.Pandoc.Definition
import Text.ParserCombinators.Parsec
import Text.Pandoc.HtmlEntities ( decodeEntities )
import Text.Pandoc.Entities ( decodeEntities )
import Text.Regex ( matchRegexAll, mkRegex, subRegex, Regex )
import Char ( toLower )
import List ( find, groupBy )

View file

@ -33,7 +33,7 @@ module Text.Pandoc.Writers.Docbook (
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Writers.HTML ( stringToSmartHtml, stringToHtml )
import Text.Pandoc.HtmlEntities ( encodeEntities )
import Text.Pandoc.Entities ( encodeEntities )
import Text.Html ( stringToHtmlString )
import Text.Regex ( mkRegex, matchRegex )
import Data.Char ( toLower, ord )