aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Shared.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Shared.hs')
-rw-r--r--src/Text/Pandoc/Shared.hs47
1 files changed, 12 insertions, 35 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 920edca7b..50abe6937 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -25,6 +25,7 @@ module Text.Pandoc.Shared (
ordNub,
findM,
-- * Text processing
+ inquotes,
tshow,
elemText,
notElemText,
@@ -68,7 +69,6 @@ module Text.Pandoc.Shared (
makeMeta,
eastAsianLineBreakFilter,
htmlSpanLikeElements,
- splitSentences,
filterIpynbOutput,
-- * TagSoup HTML handling
renderTags',
@@ -187,6 +187,10 @@ findM p = foldr go (pure Nothing)
-- Text processing
--
+-- | Wrap double quotes around a Text
+inquotes :: T.Text -> T.Text
+inquotes txt = T.cons '\"' (T.snoc txt '\"')
+
tshow :: Show a => a -> T.Text
tshow = T.pack . show
@@ -709,33 +713,6 @@ eastAsianLineBreakFilter = bottomUp go
htmlSpanLikeElements :: Set.Set T.Text
htmlSpanLikeElements = Set.fromList ["kbd", "mark", "dfn"]
--- | Returns the first sentence in a list of inlines, and the rest.
-breakSentence :: [Inline] -> ([Inline], [Inline])
-breakSentence [] = ([],[])
-breakSentence xs =
- let isSentenceEndInline (Str ys)
- | Just (_, c) <- T.unsnoc ys = c == '.' || c == '?'
- isSentenceEndInline LineBreak = True
- isSentenceEndInline _ = False
- (as, bs) = break isSentenceEndInline xs
- in case bs of
- [] -> (as, [])
- [c] -> (as ++ [c], [])
- (c:Space:cs) -> (as ++ [c], cs)
- (c:SoftBreak:cs) -> (as ++ [c], cs)
- (Str ".":Str s@(T.uncons -> Just (')',_)):cs)
- -> (as ++ [Str ".", Str s], cs)
- (x@(Str (T.stripPrefix ".)" -> Just _)):cs) -> (as ++ [x], cs)
- (LineBreak:x@(Str (T.uncons -> Just ('.',_))):cs) -> (as ++[LineBreak], x:cs)
- (c:cs) -> (as ++ [c] ++ ds, es)
- where (ds, es) = breakSentence cs
-
--- | Split a list of inlines into sentences.
-splitSentences :: [Inline] -> [[Inline]]
-splitSentences xs =
- let (sent, rest) = breakSentence xs
- in if null rest then [sent] else sent : splitSentences rest
-
-- | Process ipynb output cells. If mode is Nothing,
-- remove all output. If mode is Just format, select
-- best output for the format. If format is not ipynb,
@@ -755,17 +732,17 @@ filterIpynbOutput mode = walk go
where
rank (RawBlock (Format "html") _)
| fmt == Format "html" = 1 :: Int
- | fmt == Format "markdown" = 2
- | otherwise = 3
+ | fmt == Format "markdown" = 3
+ | otherwise = 4
rank (RawBlock (Format "latex") _)
| fmt == Format "latex" = 1
- | fmt == Format "markdown" = 2
- | otherwise = 3
+ | fmt == Format "markdown" = 3
+ | otherwise = 4
rank (RawBlock f _)
| fmt == f = 1
- | otherwise = 3
- rank (Para [Image{}]) = 1
- rank _ = 2
+ | otherwise = 4
+ rank (Para [Image{}]) = 2
+ rank _ = 3
removeANSI (CodeBlock attr code) =
CodeBlock attr (removeANSIEscapes code)
removeANSI x = x