diff options
| author | despresc <[email protected]> | 2019-11-09 23:02:03 -0500 |
|---|---|---|
| committer | despresc <[email protected]> | 2019-11-09 23:02:03 -0500 |
| commit | 7b28f927a67049370fd6854f78d9a8f04a38cd6c (patch) | |
| tree | 70acd5b285b7e453d240489b28b391cdb81edfca | |
| parent | a07e4109a45f5c466647bf87c178902434953603 (diff) | |
Finish the Writers
| -rw-r--r-- | src/Text/Pandoc/Writers/AsciiDoc.hs | 12 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/CommonMark.hs | 4 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 22 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/DokuWiki.hs | 5 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/FB2.hs | 14 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 29 |
6 files changed, 42 insertions, 44 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index e0f286529..271132575 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -24,7 +24,7 @@ import Prelude import Control.Monad.State.Strict import Data.Char (isPunctuation, isSpace) import Data.List (intercalate, intersperse) -import Data.Maybe (fromMaybe, isJust, listToMaybe) +import Data.Maybe (fromMaybe, isJust) import qualified Data.Set as Set import qualified Data.Text as T import Data.Text (Text) @@ -114,15 +114,17 @@ olMarker = do (start, style', delim) <- anyOrderedListMarker -- | True if string begins with an ordered list marker -- or would be interpreted as an AsciiDoc option command needsEscaping :: Text -> Bool -needsEscaping s = beginsWithOrderedListMarker s || isBracketed (T.unpack s) +needsEscaping s = beginsWithOrderedListMarker s || isBracketed s where beginsWithOrderedListMarker str = case runParser olMarker defaultParserState "para start" (T.take 10 str) of Left _ -> False Right _ -> True - -- TODO text: refactor - isBracketed ('[':cs) = listToMaybe (reverse cs) == Just ']' - isBracketed _ = False + isBracketed t + | Just ('[', t') <- T.uncons t + , Just (_, ']') <- T.unsnoc t' + = True + | otherwise = False -- | Convert Pandoc block element to asciidoc. blockToAsciiDoc :: PandocMonad m diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index 59a76bd18..e2d2b8e4d 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -355,7 +355,7 @@ stringToNodes opts s toSubscriptInline :: Inline -> Maybe Inline toSubscriptInline Space = Just Space toSubscriptInline (Span attr ils) = Span attr <$> traverse toSubscriptInline ils -toSubscriptInline (Str s) = Str . T.pack <$> traverse toSubscript (T.unpack s) -- TODO text: refactor +toSubscriptInline (Str s) = Str . T.pack <$> traverse toSubscript (T.unpack s) toSubscriptInline LineBreak = Just LineBreak toSubscriptInline SoftBreak = Just SoftBreak toSubscriptInline _ = Nothing @@ -363,7 +363,7 @@ toSubscriptInline _ = Nothing toSuperscriptInline :: Inline -> Maybe Inline toSuperscriptInline Space = Just Space toSuperscriptInline (Span attr ils) = Span attr <$> traverse toSuperscriptInline ils -toSuperscriptInline (Str s) = Str . T.pack <$> traverse toSuperscript (T.unpack s) -- TODO text: refactor +toSuperscriptInline (Str s) = Str . T.pack <$> traverse toSuperscript (T.unpack s) toSuperscriptInline LineBreak = Just LineBreak toSuperscriptInline SoftBreak = Just SoftBreak toSuperscriptInline _ = Nothing diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index a296b9fac..73dae56d4 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -32,6 +32,7 @@ import qualified Data.Map as M import Data.Maybe (fromMaybe, isNothing, mapMaybe, maybeToList) import qualified Data.Set as Set import qualified Data.Text as T +import qualified Data.Text.Lazy as TL import Data.Time.Clock.POSIX import Data.Digest.Pure.SHA (sha1, showDigest) import Skylighting @@ -40,7 +41,7 @@ import Text.Pandoc.BCP47 (getLang, renderLang) import Text.Pandoc.Class (PandocMonad, report, toLang) import qualified Text.Pandoc.Class as P import Data.Time -import Text.Pandoc.UTF8 (fromStringLazy) +import Text.Pandoc.UTF8 (fromTextLazy) import Text.Pandoc.Definition import Text.Pandoc.Generic import Text.Pandoc.Highlighting (highlight) @@ -890,7 +891,7 @@ blockToOpenXML' :: (PandocMonad m) => WriterOptions -> Block -> WS m [Element] blockToOpenXML' _ Null = return [] blockToOpenXML' opts (Div (ident,_classes,kvs) bs) = do stylemod <- case lookup dynamicStyleKey kvs of - Just (fromString . T.unpack -> sty) -> do -- TODO text: unhappy + Just (fromString . T.unpack -> sty) -> do modify $ \s -> s{stDynamicParaProps = Set.insert sty (stDynamicParaProps s)} @@ -1181,7 +1182,7 @@ inlineToOpenXML' _ (Span (ident,["comment-end"],kvs) _) = ] inlineToOpenXML' opts (Span (ident,classes,kvs) ils) = do stylemod <- case lookup dynamicStyleKey kvs of - Just (fromString . T.unpack -> sty) -> do -- TODO text: unhappy + Just (fromString . T.unpack -> sty) -> do modify $ \s -> s{stDynamicTextProps = Set.insert sty (stDynamicTextProps s)} @@ -1477,12 +1478,9 @@ wrapBookmark ident contents = do -- Word imposes a 40 character limit on bookmark names and requires -- that they begin with a letter. So we just use a hash of the -- identifer when otherwise we'd have an illegal bookmark name. -toBookmarkName :: T.Text -> T.Text -- TODO text: refactor -toBookmarkName = T.pack . toBookmarkName' . T.unpack - -toBookmarkName' :: String -> String -toBookmarkName' s = - case s of - (c:_) | isLetter c - , length s <= 40 -> s - _ -> 'X' : drop 1 (showDigest (sha1 (fromStringLazy s))) +toBookmarkName :: T.Text -> T.Text +toBookmarkName s + | Just (c, _) <- T.uncons s + , isLetter c + , T.length s <= 40 = s + | otherwise = T.pack $ 'X' : drop 1 (showDigest (sha1 (fromTextLazy $ TL.fromStrict s))) diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 7fd679cc6..541939f3b 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -1,5 +1,5 @@ {-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE OverloadedStrings #-} -- TODO text: possibly remove +{-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Writers.DokuWiki Copyright : Copyright (C) 2008-2019 John MacFarlane @@ -179,7 +179,7 @@ blockToDokuWiki opts (Table capt aligns _ headers rows) = do else zipWithM (tableItemToDokuWiki opts) aligns headers rows' <- mapM (zipWithM (tableItemToDokuWiki opts) aligns) rows let widths = map (maximum . map T.length) $ transpose (headers':rows') - let padTo (width, al) s = -- TODO text: replace with text pad? + let padTo (width, al) s = case width - T.length s of x | x > 0 -> if al == AlignLeft || al == AlignDefault @@ -345,7 +345,6 @@ backSlashLineBreaks :: [Text] -> Text backSlashLineBreaks ls = vcatBackSlash $ map (T.pack . escape . T.unpack) ls where vcatBackSlash = T.intercalate "\\\\ \\\\ " -- simulate paragraphs. - -- TODO text: refactor escape ['\n'] = "" -- remove trailing newlines escape ('\n':cs) = "\\\\ " <> escape cs escape (c:cs) = c : escape cs diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 343927509..8cb29c269 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -1,6 +1,6 @@ {-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE PatternGuards #-} -{-# LANGUAGE OverloadedStrings #-} -- TODO text: possibly remove +{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Writers.FB2 Copyright : Copyright (C) 2011-2012 Sergey Astanin @@ -100,8 +100,8 @@ pandocToFB2 opts (Pandoc meta blocks) = do description :: PandocMonad m => Meta -> FBM m Content description meta' = do let genre = case lookupMetaString "genre" meta' of - "" -> el "genre" ("unrecognised" :: String) -- TODO text: refactor - s -> el "genre" (T.unpack s) -- TODO text: refactor + "" -> el "genre" ("unrecognised" :: String) + s -> el "genre" (T.unpack s) bt <- booktitle meta' let as = authors meta' dd <- docdate meta' @@ -124,7 +124,7 @@ description meta' = do return $ el "description" [ el "title-info" (genre : (as ++ bt ++ annotation ++ dd ++ coverpage ++ lang)) - , el "document-info" [el "program-used" ("pandoc" :: String)] -- TODO text: refactor + , el "document-info" [el "program-used" ("pandoc" :: String)] ] booktitle :: PandocMonad m => Meta -> FBM m [Content] @@ -259,7 +259,7 @@ readDataURI :: Text -- ^ URI readDataURI uri = case T.stripPrefix "data:" uri of Nothing -> Nothing - Just rest -> -- TODO text: refactor (dropWhileEnd?) + Just rest -> let meta = T.takeWhile (/= ',') rest -- without trailing ',' uridata = T.drop (T.length meta + 1) rest parts = T.split (== ';') meta @@ -470,7 +470,7 @@ insertImage immode (Image _ alt (url,ttl)) = do el "image" $ [ attr ("l","href") ("#" <> fname) , attr ("l","type") (tshow immode) - , uattr "alt" (T.pack $ cMap plain alt) ] -- TODO text: refactor + , uattr "alt" (T.pack $ cMap plain alt) ] ++ ttlattr insertImage _ _ = error "unexpected inline instead of image" diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 4f17ef81e..9a826061f 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -110,22 +110,21 @@ defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False, -- Helpers to render HTML with the appropriate function. -strToHtml :: Text -> Html -- TODO text: refactor +strToHtml :: Text -> Html strToHtml = strToHtml' . T.unpack - -strToHtml' :: String -> Html -strToHtml' ('\'':xs) = preEscapedString "\'" `mappend` strToHtml' xs -strToHtml' ('"' :xs) = preEscapedString "\"" `mappend` strToHtml' xs -strToHtml' (x:xs) | needsVariationSelector x - = preEscapedString [x, '\xFE0E'] `mappend` - case xs of - ('\xFE0E':ys) -> strToHtml' ys - _ -> strToHtml' xs -strToHtml' xs@(_:_) = case break (\c -> c == '\'' || c == '"' || - needsVariationSelector c) xs of - (_ ,[]) -> toHtml xs - (ys,zs) -> toHtml ys `mappend` strToHtml' zs -strToHtml' [] = "" + where + strToHtml' ('\'':xs) = preEscapedString "\'" `mappend` strToHtml' xs + strToHtml' ('"' :xs) = preEscapedString "\"" `mappend` strToHtml' xs + strToHtml' (x:xs) | needsVariationSelector x + = preEscapedString [x, '\xFE0E'] `mappend` + case xs of + ('\xFE0E':ys) -> strToHtml' ys + _ -> strToHtml' xs + strToHtml' xs@(_:_) = case break (\c -> c == '\'' || c == '"' || + needsVariationSelector c) xs of + (_ ,[]) -> toHtml xs + (ys,zs) -> toHtml ys `mappend` strToHtml' zs + strToHtml' [] = "" -- See #5469: this prevents iOS from substituting emojis. needsVariationSelector :: Char -> Bool |
