aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Entities.hs10
-rw-r--r--src/Text/Pandoc/Shared.hs6
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs22
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs14
4 files changed, 26 insertions, 26 deletions
diff --git a/src/Text/Pandoc/Entities.hs b/src/Text/Pandoc/Entities.hs
index e91cf3864..703d4d230 100644
--- a/src/Text/Pandoc/Entities.hs
+++ b/src/Text/Pandoc/Entities.hs
@@ -31,9 +31,9 @@ and vice versa.
module Text.Pandoc.Entities (
charToEntity,
charToNumericalEntity,
- encodeEntities,
decodeEntities,
escapeSGMLChar,
+ escapeSGMLString,
characterEntity
) where
import Data.Char ( chr, ord )
@@ -100,12 +100,12 @@ needsEscaping :: Char -> Bool
needsEscaping c = c `elem` "&<>\""
-- | Escape string as needed for SGML. Entity references are not preserved.
-encodeEntities :: String -> String
-encodeEntities "" = ""
-encodeEntities str =
+escapeSGMLString :: String -> String
+escapeSGMLString "" = ""
+escapeSGMLString str =
case break needsEscaping str of
(okay, "") -> okay
- (okay, (c:cs)) -> okay ++ escapeSGMLChar c ++ encodeEntities cs
+ (okay, (c:cs)) -> okay ++ escapeSGMLChar c ++ escapeSGMLString cs
-- | Convert entities in a string to characters.
decodeEntities :: String -> String
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 83b64b4fb..11faced5d 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -72,7 +72,7 @@ module Text.Pandoc.Shared (
) where
import Text.Pandoc.Definition
import Text.ParserCombinators.Parsec as Parsec
-import Text.Pandoc.Entities ( decodeEntities, encodeEntities )
+import Text.Pandoc.Entities ( decodeEntities, escapeSGMLString )
import Text.PrettyPrint.HughesPJ as PP ( text, char, (<>),
($$), nest, Doc, isEmpty )
import Data.Char ( toLower, ord )
@@ -524,8 +524,8 @@ replaceRefLinksInline keytable other = other
-- | Return a text object with a string of formatted SGML attributes.
attributeList :: [(String, String)] -> Doc
attributeList = text . concatMap
- (\(a, b) -> " " ++ encodeEntities a ++ "=\"" ++
- encodeEntities b ++ "\"")
+ (\(a, b) -> " " ++ escapeSGMLString a ++ "=\"" ++
+ escapeSGMLString b ++ "\"")
-- | Put the supplied contents between start and end tags of tagType,
-- with specified attributes and (if specified) indentation.
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 405b2978a..0c1d35e63 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -32,7 +32,7 @@ module Text.Pandoc.Writers.Docbook (
) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
-import Text.Pandoc.Entities ( encodeEntities )
+import Text.Pandoc.Entities ( escapeSGMLString )
import Data.Char ( toLower, ord )
import Data.List ( isPrefixOf, partition, drop )
import Text.PrettyPrint.HughesPJ hiding ( Str )
@@ -64,8 +64,8 @@ authorToDocbook name = inTagsIndented "author" $
then -- last name first
let (lastname, rest) = break (==',') name
firstname = removeLeadingSpace rest in
- inTagsSimple "firstname" (text $ encodeEntities firstname) <>
- inTagsSimple "surname" (text $ encodeEntities lastname)
+ inTagsSimple "firstname" (text $ escapeSGMLString firstname) <>
+ inTagsSimple "surname" (text $ escapeSGMLString lastname)
else -- last name last
let namewords = words name
lengthname = length namewords
@@ -73,8 +73,8 @@ authorToDocbook name = inTagsIndented "author" $
0 -> ("","")
1 -> ("", name)
n -> (joinWithSep " " (take (n-1) namewords), last namewords) in
- inTagsSimple "firstname" (text $ encodeEntities firstname) $$
- inTagsSimple "surname" (text $ encodeEntities lastname)
+ inTagsSimple "firstname" (text $ escapeSGMLString firstname) $$
+ inTagsSimple "surname" (text $ escapeSGMLString lastname)
-- | Convert Pandoc document to string in Docbook format.
writeDocbook :: WriterOptions -> Pandoc -> String
@@ -86,7 +86,7 @@ writeDocbook opts (Pandoc (Meta title authors date) blocks) =
then inTagsIndented "articleinfo" $
(inTagsSimple "title" (wrap opts title)) $$
(vcat (map authorToDocbook authors)) $$
- (inTagsSimple "date" (text $ encodeEntities date))
+ (inTagsSimple "date" (text $ escapeSGMLString date))
else empty
blocks' = replaceReferenceLinks blocks
(noteBlocks, blocks'') = partition isNoteBlock blocks'
@@ -141,7 +141,7 @@ blockToDocbook opts (Para lst) =
blockToDocbook opts (BlockQuote blocks) =
inTagsIndented "blockquote" (blocksToDocbook opts blocks)
blockToDocbook opts (CodeBlock str) =
- text "<screen>\n" <> text (encodeEntities str) <> text "\n</screen>"
+ text "<screen>\n" <> text (escapeSGMLString str) <> text "\n</screen>"
blockToDocbook opts (BulletList lst) =
inTagsIndented "itemizedlist" $ listItemsToDocbook opts lst
blockToDocbook opts (OrderedList lst) =
@@ -198,7 +198,7 @@ inlinesToDocbook opts lst = hcat (map (inlineToDocbook opts) lst)
-- | Convert an inline element to Docbook.
inlineToDocbook :: WriterOptions -> Inline -> Doc
-inlineToDocbook opts (Str str) = text $ encodeEntities str
+inlineToDocbook opts (Str str) = text $ escapeSGMLString str
inlineToDocbook opts (Emph lst) =
inTagsSimple "emphasis" (inlinesToDocbook opts lst)
inlineToDocbook opts (Strong lst) =
@@ -211,7 +211,7 @@ inlineToDocbook opts Ellipses = text "&#8230;"
inlineToDocbook opts EmDash = text "&#8212;"
inlineToDocbook opts EnDash = text "&#8211;"
inlineToDocbook opts (Code str) =
- inTagsSimple "literal" $ text (encodeEntities str)
+ inTagsSimple "literal" $ text (escapeSGMLString str)
inlineToDocbook opts (TeX str) = inlineToDocbook opts (Code str)
inlineToDocbook opts (HtmlInline str) = empty
inlineToDocbook opts LineBreak =
@@ -219,7 +219,7 @@ inlineToDocbook opts LineBreak =
inlineToDocbook opts Space = char ' '
inlineToDocbook opts (Link txt (Src src tit)) =
if isPrefixOf "mailto:" src
- then inTagsSimple "email" $ text (encodeEntities $ drop 7 src)
+ then inTagsSimple "email" $ text (escapeSGMLString $ drop 7 src)
else inTags False "ulink" [("url", src)] $ inlinesToDocbook opts txt
inlineToDocbook opts (Link text (Ref ref)) = empty -- shouldn't occur
inlineToDocbook opts (Image alt (Src src tit)) =
@@ -227,7 +227,7 @@ inlineToDocbook opts (Image alt (Src src tit)) =
then empty
else inTagsIndented "objectinfo" $
inTagsIndented "title"
- (text $ encodeEntities tit) in
+ (text $ escapeSGMLString tit) in
inTagsIndented "inlinemediaobject" $
inTagsIndented "imageobject" $
titleDoc $$ selfClosingTag "imagedata" [("fileref", src)]
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 8a654e3c9..a7ee9c0f3 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -32,7 +32,7 @@ module Text.Pandoc.Writers.HTML (
) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
-import Text.Pandoc.Entities ( encodeEntities )
+import Text.Pandoc.Entities ( escapeSGMLString )
import Text.Regex ( mkRegex, matchRegex )
import Numeric ( showHex )
import Data.Char ( ord, toLower )
@@ -127,11 +127,11 @@ htmlHeader opts (Meta title authors date) =
then empty
else selfClosingTag "meta" [("name", "author"),
("content",
- joinWithSep ", " (map encodeEntities authors))]
+ joinWithSep ", " (map escapeSGMLString authors))]
datetext = if (date == "")
then empty
else selfClosingTag "meta" [("name", "date"),
- ("content", encodeEntities date)] in
+ ("content", escapeSGMLString date)] in
text (writerHeader opts) $$ authortext $$ datetext $$ titletext $$
text "</head>\n<body>"
@@ -168,7 +168,7 @@ blockToHtml opts (Note ref lst) =
(text "&#8617;")
blockToHtml opts (Key _ _) = empty
blockToHtml opts (CodeBlock str) =
- text "<pre><code>" <> text (encodeEntities str) <> text "\n</code></pre>"
+ text "<pre><code>" <> text (escapeSGMLString str) <> text "\n</code></pre>"
blockToHtml opts (RawHtml str) = text str
blockToHtml opts (BulletList lst) =
let attribs = if (writerIncremental opts)
@@ -234,7 +234,7 @@ inlineToHtml opts (Emph lst) =
inlineToHtml opts (Strong lst) =
inTagsSimple "strong" (inlineListToHtml opts lst)
inlineToHtml opts (Code str) =
- inTagsSimple "code" $ text (encodeEntities str)
+ inTagsSimple "code" $ text (escapeSGMLString str)
inlineToHtml opts (Quoted SingleQuote lst) =
text "&lsquo;" <> (inlineListToHtml opts lst) <> text "&rsquo;"
inlineToHtml opts (Quoted DoubleQuote lst) =
@@ -243,8 +243,8 @@ inlineToHtml opts EmDash = text "&mdash;"
inlineToHtml opts EnDash = text "&ndash;"
inlineToHtml opts Ellipses = text "&hellip;"
inlineToHtml opts Apostrophe = text "&rsquo;"
-inlineToHtml opts (Str str) = text $ encodeEntities str
-inlineToHtml opts (TeX str) = text $ encodeEntities str
+inlineToHtml opts (Str str) = text $ escapeSGMLString str
+inlineToHtml opts (TeX str) = text $ escapeSGMLString str
inlineToHtml opts (HtmlInline str) = text str
inlineToHtml opts (LineBreak) = selfClosingTag "br" []
inlineToHtml opts Space = space