Muse writer: use lightweight markup when possible
This commit is contained in:
parent
746c30971e
commit
6ea6011ca6
3 changed files with 198 additions and 69 deletions
|
@ -46,7 +46,7 @@ module Text.Pandoc.Writers.Muse (writeMuse) where
|
||||||
import Prelude
|
import Prelude
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Control.Monad.State.Strict
|
import Control.Monad.State.Strict
|
||||||
import Data.Char (isSpace, isDigit, isAsciiUpper, isAsciiLower)
|
import Data.Char (isSpace, isAlphaNum, isDigit, isAsciiUpper, isAsciiLower)
|
||||||
import Data.Default
|
import Data.Default
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Data.List (intersperse, transpose, isInfixOf)
|
import Data.List (intersperse, transpose, isInfixOf)
|
||||||
|
@ -74,16 +74,20 @@ data WriterEnv =
|
||||||
, envInsideLinkDescription :: Bool -- ^ Escape ] if True
|
, envInsideLinkDescription :: Bool -- ^ Escape ] if True
|
||||||
, envAfterSpace :: Bool -- ^ There is whitespace (not just newline) before
|
, envAfterSpace :: Bool -- ^ There is whitespace (not just newline) before
|
||||||
, envOneLine :: Bool -- ^ True if newlines are not allowed
|
, envOneLine :: Bool -- ^ True if newlines are not allowed
|
||||||
|
, envInsideAsterisks :: Bool -- ^ True if outer element is emphasis with asterisks
|
||||||
|
, envNearAsterisks :: Bool -- ^ Rendering inline near asterisks
|
||||||
}
|
}
|
||||||
|
|
||||||
data WriterState =
|
data WriterState =
|
||||||
WriterState { stNotes :: Notes
|
WriterState { stNotes :: Notes
|
||||||
, stIds :: Set.Set String
|
, stIds :: Set.Set String
|
||||||
|
, stUseTags :: Bool -- ^ Use tags for emphasis, for example because previous character is a letter
|
||||||
}
|
}
|
||||||
|
|
||||||
instance Default WriterState
|
instance Default WriterState
|
||||||
where def = WriterState { stNotes = []
|
where def = WriterState { stNotes = []
|
||||||
, stIds = Set.empty
|
, stIds = Set.empty
|
||||||
|
, stUseTags = False
|
||||||
}
|
}
|
||||||
|
|
||||||
evalMuse :: PandocMonad m => Muse m a -> WriterEnv -> WriterState -> m a
|
evalMuse :: PandocMonad m => Muse m a -> WriterEnv -> WriterState -> m a
|
||||||
|
@ -103,6 +107,8 @@ writeMuse opts document =
|
||||||
, envInsideLinkDescription = False
|
, envInsideLinkDescription = False
|
||||||
, envAfterSpace = False
|
, envAfterSpace = False
|
||||||
, envOneLine = False
|
, envOneLine = False
|
||||||
|
, envInsideAsterisks = False
|
||||||
|
, envNearAsterisks = False
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Return Muse representation of document.
|
-- | Return Muse representation of document.
|
||||||
|
@ -212,6 +218,7 @@ blockToMuse (BulletList items) = do
|
||||||
=> [Block]
|
=> [Block]
|
||||||
-> Muse m Doc
|
-> Muse m Doc
|
||||||
bulletListItemToMuse item = do
|
bulletListItemToMuse item = do
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
contents <- blockListToMuse item
|
contents <- blockListToMuse item
|
||||||
return $ hang 2 "- " contents
|
return $ hang 2 "- " contents
|
||||||
blockToMuse (DefinitionList items) = do
|
blockToMuse (DefinitionList items) = do
|
||||||
|
@ -223,6 +230,7 @@ blockToMuse (DefinitionList items) = do
|
||||||
=> ([Inline], [[Block]])
|
=> ([Inline], [[Block]])
|
||||||
-> Muse m Doc
|
-> Muse m Doc
|
||||||
definitionListItemToMuse (label, defs) = do
|
definitionListItemToMuse (label, defs) = do
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
label' <- local (\env -> env { envOneLine = True, envAfterSpace = True }) $ inlineListToMuse' label
|
label' <- local (\env -> env { envOneLine = True, envAfterSpace = True }) $ inlineListToMuse' label
|
||||||
contents <- vcat <$> mapM descriptionToMuse defs
|
contents <- vcat <$> mapM descriptionToMuse defs
|
||||||
let ind = offset label'
|
let ind = offset label'
|
||||||
|
@ -401,6 +409,17 @@ fixNotes (Space : n@Note{} : rest) = Str " " : n : fixNotes rest
|
||||||
fixNotes (SoftBreak : n@Note{} : rest) = Str " " : n : fixNotes rest
|
fixNotes (SoftBreak : n@Note{} : rest) = Str " " : n : fixNotes rest
|
||||||
fixNotes (x:xs) = x : fixNotes xs
|
fixNotes (x:xs) = x : fixNotes xs
|
||||||
|
|
||||||
|
startsWithSpace :: [Inline] -> Bool
|
||||||
|
startsWithSpace (Space:_) = True
|
||||||
|
startsWithSpace (SoftBreak:_) = True
|
||||||
|
startsWithSpace _ = False
|
||||||
|
|
||||||
|
endsWithSpace :: [Inline] -> Bool
|
||||||
|
endsWithSpace [Space] = True
|
||||||
|
endsWithSpace [SoftBreak] = True
|
||||||
|
endsWithSpace (_:xs) = endsWithSpace xs
|
||||||
|
endsWithSpace [] = False
|
||||||
|
|
||||||
urlEscapeBrackets :: String -> String
|
urlEscapeBrackets :: String -> String
|
||||||
urlEscapeBrackets (']':xs) = '%':'5':'D':urlEscapeBrackets xs
|
urlEscapeBrackets (']':xs) = '%':'5':'D':urlEscapeBrackets xs
|
||||||
urlEscapeBrackets (x:xs) = x:urlEscapeBrackets xs
|
urlEscapeBrackets (x:xs) = x:urlEscapeBrackets xs
|
||||||
|
@ -409,9 +428,9 @@ urlEscapeBrackets [] = []
|
||||||
isHorizontalRule :: String -> Bool
|
isHorizontalRule :: String -> Bool
|
||||||
isHorizontalRule s = length s >= 4 && all (== '-') s
|
isHorizontalRule s = length s >= 4 && all (== '-') s
|
||||||
|
|
||||||
startsWithSpace :: String -> Bool
|
stringStartsWithSpace :: String -> Bool
|
||||||
startsWithSpace (x:_) = isSpace x
|
stringStartsWithSpace (x:_) = isSpace x
|
||||||
startsWithSpace [] = False
|
stringStartsWithSpace [] = False
|
||||||
|
|
||||||
fixOrEscape :: Bool -> Inline -> Bool
|
fixOrEscape :: Bool -> Inline -> Bool
|
||||||
fixOrEscape sp (Str "-") = sp
|
fixOrEscape sp (Str "-") = sp
|
||||||
|
@ -420,11 +439,19 @@ fixOrEscape _ (Str ">") = True
|
||||||
fixOrEscape sp (Str s) = (sp && (startsWithMarker isDigit s ||
|
fixOrEscape sp (Str s) = (sp && (startsWithMarker isDigit s ||
|
||||||
startsWithMarker isAsciiLower s ||
|
startsWithMarker isAsciiLower s ||
|
||||||
startsWithMarker isAsciiUpper s))
|
startsWithMarker isAsciiUpper s))
|
||||||
|| isHorizontalRule s || startsWithSpace s
|
|| isHorizontalRule s || stringStartsWithSpace s
|
||||||
fixOrEscape _ Space = True
|
fixOrEscape _ Space = True
|
||||||
fixOrEscape _ SoftBreak = True
|
fixOrEscape _ SoftBreak = True
|
||||||
fixOrEscape _ _ = False
|
fixOrEscape _ _ = False
|
||||||
|
|
||||||
|
inlineListStartsWithAlnum :: PandocMonad m
|
||||||
|
=> [Inline]
|
||||||
|
-> Muse m Bool
|
||||||
|
inlineListStartsWithAlnum (Str s:_) = do
|
||||||
|
esc <- shouldEscapeString s
|
||||||
|
return $ esc || isAlphaNum (head s)
|
||||||
|
inlineListStartsWithAlnum _ = return False
|
||||||
|
|
||||||
-- | Convert list of Pandoc inline elements to Muse
|
-- | Convert list of Pandoc inline elements to Muse
|
||||||
renderInlineList :: PandocMonad m
|
renderInlineList :: PandocMonad m
|
||||||
=> [Inline]
|
=> [Inline]
|
||||||
|
@ -436,11 +463,22 @@ renderInlineList (x:xs) = do
|
||||||
start <- asks envInlineStart
|
start <- asks envInlineStart
|
||||||
afterSpace <- asks envAfterSpace
|
afterSpace <- asks envAfterSpace
|
||||||
topLevel <- asks envTopLevel
|
topLevel <- asks envTopLevel
|
||||||
r <- local (\env -> env { envInlineStart = False }) $ inlineToMuse x
|
insideAsterisks <- asks envInsideAsterisks
|
||||||
|
nearAsterisks <- asks envNearAsterisks
|
||||||
|
useTags <- gets stUseTags
|
||||||
|
alnumNext <- inlineListStartsWithAlnum xs
|
||||||
|
let newUseTags = useTags || alnumNext
|
||||||
|
modify $ \st -> st { stUseTags = newUseTags }
|
||||||
|
|
||||||
|
r <- local (\env -> env { envInlineStart = False
|
||||||
|
, envInsideAsterisks = False
|
||||||
|
, envNearAsterisks = nearAsterisks || (null xs && insideAsterisks)
|
||||||
|
}) $ inlineToMuse x
|
||||||
opts <- asks envOptions
|
opts <- asks envOptions
|
||||||
let isNewline = (x == SoftBreak && writerWrapText opts == WrapPreserve) || x == LineBreak
|
let isNewline = (x == SoftBreak && writerWrapText opts == WrapPreserve) || x == LineBreak
|
||||||
lst' <- local (\env -> env { envInlineStart = isNewline
|
lst' <- local (\env -> env { envInlineStart = isNewline
|
||||||
, envAfterSpace = x == Space || (not topLevel && isNewline)
|
, envAfterSpace = x == Space || (not topLevel && isNewline)
|
||||||
|
, envNearAsterisks = False
|
||||||
}) $ renderInlineList xs
|
}) $ renderInlineList xs
|
||||||
if start && fixOrEscape afterSpace x
|
if start && fixOrEscape afterSpace x
|
||||||
then pure (text "<verbatim></verbatim>" <> r <> lst')
|
then pure (text "<verbatim></verbatim>" <> r <> lst')
|
||||||
|
@ -452,7 +490,9 @@ inlineListToMuse :: PandocMonad m
|
||||||
-> Muse m Doc
|
-> Muse m Doc
|
||||||
inlineListToMuse lst = do
|
inlineListToMuse lst = do
|
||||||
lst' <- (normalizeInlineList . fixNotes) <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst)
|
lst' <- (normalizeInlineList . fixNotes) <$> preprocessInlineList (map (removeKeyValues . replaceSmallCaps) lst)
|
||||||
renderInlineList lst'
|
insideAsterisks <- asks envInsideAsterisks
|
||||||
|
modify $ \st -> st { stUseTags = False } -- Previous character is likely a '>' or some other markup
|
||||||
|
local (\env -> env { envNearAsterisks = insideAsterisks }) $ renderInlineList lst'
|
||||||
|
|
||||||
inlineListToMuse' :: PandocMonad m => [Inline] -> Muse m Doc
|
inlineListToMuse' :: PandocMonad m => [Inline] -> Muse m Doc
|
||||||
inlineListToMuse' lst = do
|
inlineListToMuse' lst = do
|
||||||
|
@ -466,52 +506,112 @@ inlineListToMuse' lst = do
|
||||||
inlineToMuse :: PandocMonad m
|
inlineToMuse :: PandocMonad m
|
||||||
=> Inline
|
=> Inline
|
||||||
-> Muse m Doc
|
-> Muse m Doc
|
||||||
inlineToMuse (Str str) =
|
inlineToMuse (Str str) = do
|
||||||
text <$> conditionalEscapeString str
|
escapedStr <- conditionalEscapeString str
|
||||||
|
let useTags = isAlphaNum $ last escapedStr -- escapedStr is never empty because empty strings are escaped
|
||||||
|
modify $ \st -> st { stUseTags = useTags }
|
||||||
|
return $ text escapedStr
|
||||||
|
inlineToMuse (Emph [Strong lst]) = do
|
||||||
|
useTags <- gets stUseTags
|
||||||
|
if useTags
|
||||||
|
then do contents <- local (\env -> env { envInsideAsterisks = True }) $ inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
|
return $ "<em>**" <> contents <> "**</em>"
|
||||||
|
else if null lst || startsWithSpace lst || endsWithSpace lst
|
||||||
|
then do
|
||||||
|
contents <- local (\env -> env { envInsideAsterisks = False }) $ inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = True }
|
||||||
|
return $ "*<strong>" <> contents <> "</strong>*"
|
||||||
|
else do
|
||||||
|
contents <- local (\env -> env { envInsideAsterisks = True }) $ inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = True }
|
||||||
|
return $ "***" <> contents <> "***"
|
||||||
inlineToMuse (Emph lst) = do
|
inlineToMuse (Emph lst) = do
|
||||||
contents <- inlineListToMuse lst
|
useTags <- gets stUseTags
|
||||||
return $ "<em>" <> contents <> "</em>"
|
if useTags || null lst || startsWithSpace lst || endsWithSpace lst
|
||||||
|
then do contents <- inlineListToMuse lst
|
||||||
|
return $ "<em>" <> contents <> "</em>"
|
||||||
|
else do contents <- local (\env -> env { envInsideAsterisks = True }) $ inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = True }
|
||||||
|
return $ "*" <> contents <> "*"
|
||||||
|
inlineToMuse (Strong [Emph lst]) = do
|
||||||
|
useTags <- gets stUseTags
|
||||||
|
if useTags
|
||||||
|
then do contents <- local (\env -> env { envInsideAsterisks = True }) $ inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
|
return $ "<strong>*" <> contents <> "*</strong>"
|
||||||
|
else if null lst || startsWithSpace lst || endsWithSpace lst
|
||||||
|
then do
|
||||||
|
contents <- local (\env -> env { envInsideAsterisks = False }) $ inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = True }
|
||||||
|
return $ "**<em>" <> contents <> "</em>**"
|
||||||
|
else do
|
||||||
|
contents <- local (\env -> env { envInsideAsterisks = True }) $ inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = True }
|
||||||
|
return $ "***" <> contents <> "***"
|
||||||
inlineToMuse (Strong lst) = do
|
inlineToMuse (Strong lst) = do
|
||||||
contents <- inlineListToMuse lst
|
useTags <- gets stUseTags
|
||||||
return $ "<strong>" <> contents <> "</strong>"
|
if useTags || null lst || startsWithSpace lst || endsWithSpace lst
|
||||||
|
then do contents <- inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
|
return $ "<strong>" <> contents <> "</strong>"
|
||||||
|
else do contents <- local (\env -> env { envInsideAsterisks = True }) $ inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = True }
|
||||||
|
return $ "**" <> contents <> "**"
|
||||||
inlineToMuse (Strikeout lst) = do
|
inlineToMuse (Strikeout lst) = do
|
||||||
contents <- inlineListToMuse lst
|
contents <- inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "<del>" <> contents <> "</del>"
|
return $ "<del>" <> contents <> "</del>"
|
||||||
inlineToMuse (Superscript lst) = do
|
inlineToMuse (Superscript lst) = do
|
||||||
contents <- inlineListToMuse lst
|
contents <- inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "<sup>" <> contents <> "</sup>"
|
return $ "<sup>" <> contents <> "</sup>"
|
||||||
inlineToMuse (Subscript lst) = do
|
inlineToMuse (Subscript lst) = do
|
||||||
contents <- inlineListToMuse lst
|
contents <- inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "<sub>" <> contents <> "</sub>"
|
return $ "<sub>" <> contents <> "</sub>"
|
||||||
inlineToMuse SmallCaps {} =
|
inlineToMuse SmallCaps {} =
|
||||||
fail "SmallCaps should be expanded before normalization"
|
fail "SmallCaps should be expanded before normalization"
|
||||||
inlineToMuse (Quoted SingleQuote lst) = do
|
inlineToMuse (Quoted SingleQuote lst) = do
|
||||||
contents <- inlineListToMuse lst
|
contents <- inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "‘" <> contents <> "’"
|
return $ "‘" <> contents <> "’"
|
||||||
inlineToMuse (Quoted DoubleQuote lst) = do
|
inlineToMuse (Quoted DoubleQuote lst) = do
|
||||||
contents <- inlineListToMuse lst
|
contents <- inlineListToMuse lst
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "“" <> contents <> "”"
|
return $ "“" <> contents <> "”"
|
||||||
inlineToMuse Cite {} =
|
inlineToMuse Cite {} =
|
||||||
fail "Citations should be expanded before normalization"
|
fail "Citations should be expanded before normalization"
|
||||||
inlineToMuse (Code _ str) = return $
|
inlineToMuse (Code _ str) = do
|
||||||
"<code>" <> text (substitute "</code>" "<</code><code>/code>" str) <> "</code>"
|
useTags <- gets stUseTags
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
|
return $ if useTags || null str || '=' `elem` str || isSpace (head str) || isSpace (last str)
|
||||||
|
then "<code>" <> text (substitute "</code>" "<</code><code>/code>" str) <> "</code>"
|
||||||
|
else "=" <> text str <> "="
|
||||||
inlineToMuse Math{} =
|
inlineToMuse Math{} =
|
||||||
fail "Math should be expanded before normalization"
|
fail "Math should be expanded before normalization"
|
||||||
inlineToMuse (RawInline (Format f) str) =
|
inlineToMuse (RawInline (Format f) str) = do
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "<literal style=\"" <> text f <> "\">" <> text str <> "</literal>"
|
return $ "<literal style=\"" <> text f <> "\">" <> text str <> "</literal>"
|
||||||
inlineToMuse LineBreak = do
|
inlineToMuse LineBreak = do
|
||||||
oneline <- asks envOneLine
|
oneline <- asks envOneLine
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ if oneline then "<br>" else "<br>" <> cr
|
return $ if oneline then "<br>" else "<br>" <> cr
|
||||||
inlineToMuse Space = return space
|
inlineToMuse Space = do
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
|
return space
|
||||||
inlineToMuse SoftBreak = do
|
inlineToMuse SoftBreak = do
|
||||||
oneline <- asks envOneLine
|
oneline <- asks envOneLine
|
||||||
wrapText <- asks $ writerWrapText . envOptions
|
wrapText <- asks $ writerWrapText . envOptions
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ if not oneline && wrapText == WrapPreserve then cr else space
|
return $ if not oneline && wrapText == WrapPreserve then cr else space
|
||||||
inlineToMuse (Link _ txt (src, _)) =
|
inlineToMuse (Link _ txt (src, _)) =
|
||||||
case txt of
|
case txt of
|
||||||
[Str x] | escapeURI x == src ->
|
[Str x] | escapeURI x == src -> do
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "[[" <> text (escapeLink x) <> "]]"
|
return $ "[[" <> text (escapeLink x) <> "]]"
|
||||||
_ -> do contents <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse txt
|
_ -> do contents <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse txt
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "[[" <> text (escapeLink src) <> "][" <> contents <> "]]"
|
return $ "[[" <> text (escapeLink src) <> "][" <> contents <> "]]"
|
||||||
where escapeLink lnk = if isImageUrl lnk then "URL:" ++ urlEscapeBrackets lnk else urlEscapeBrackets lnk
|
where escapeLink lnk = if isImageUrl lnk then "URL:" ++ urlEscapeBrackets lnk else urlEscapeBrackets lnk
|
||||||
-- Taken from muse-image-regexp defined in Emacs Muse file lisp/muse-regexps.el
|
-- Taken from muse-image-regexp defined in Emacs Muse file lisp/muse-regexps.el
|
||||||
|
@ -537,11 +637,14 @@ inlineToMuse (Image attr@(_, classes, _) inlines (source, title)) = do
|
||||||
let rightalign = if "align-right" `elem` classes
|
let rightalign = if "align-right" `elem` classes
|
||||||
then " r"
|
then " r"
|
||||||
else ""
|
else ""
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ "[[" <> text (urlEscapeBrackets source ++ width ++ leftalign ++ rightalign) <> "]" <> title' <> "]"
|
return $ "[[" <> text (urlEscapeBrackets source ++ width ++ leftalign ++ rightalign) <> "]" <> title' <> "]"
|
||||||
inlineToMuse (Note contents) = do
|
inlineToMuse (Note contents) = do
|
||||||
-- add to notes in state
|
-- add to notes in state
|
||||||
notes <- gets stNotes
|
notes <- gets stNotes
|
||||||
modify $ \st -> st { stNotes = contents:notes }
|
modify $ \st -> st { stNotes = contents:notes
|
||||||
|
, stUseTags = False
|
||||||
|
}
|
||||||
let ref = show $ length notes + 1
|
let ref = show $ length notes + 1
|
||||||
return $ "[" <> text ref <> "]"
|
return $ "[" <> text ref <> "]"
|
||||||
inlineToMuse (Span (anchor,names,_) inlines) = do
|
inlineToMuse (Span (anchor,names,_) inlines) = do
|
||||||
|
@ -549,6 +652,7 @@ inlineToMuse (Span (anchor,names,_) inlines) = do
|
||||||
let anchorDoc = if null anchor
|
let anchorDoc = if null anchor
|
||||||
then mempty
|
then mempty
|
||||||
else text ('#':anchor) <> space
|
else text ('#':anchor) <> space
|
||||||
|
modify $ \st -> st { stUseTags = False }
|
||||||
return $ anchorDoc <> (if null inlines && not (null anchor)
|
return $ anchorDoc <> (if null inlines && not (null anchor)
|
||||||
then mempty
|
then mempty
|
||||||
else (if null names
|
else (if null names
|
||||||
|
|
|
@ -354,23 +354,51 @@ tests = [ testGroup "block elements"
|
||||||
, "do not escape ; inside paragraph" =: text "foo ; bar" =?> "foo ; bar"
|
, "do not escape ; inside paragraph" =: text "foo ; bar" =?> "foo ; bar"
|
||||||
]
|
]
|
||||||
, testGroup "emphasis"
|
, testGroup "emphasis"
|
||||||
[ "emph" =: emph (text "foo") =?> "<em>foo</em>"
|
[ "emphasis" =: emph (text "foo") =?> "*foo*"
|
||||||
, "strong" =: strong (text "foo") =?> "<strong>foo</strong>"
|
, "emphasis inside word" =: text "foo" <> emph (text "bar") <> text "baz" =?> "foo<em>bar</em>baz"
|
||||||
|
, "emphasis before comma" =: emph (text "foo") <> text ", bar" =?> "*foo*, bar"
|
||||||
|
, "emphasis before period" =: emph (text "foobar") <> text "." =?> "*foobar*."
|
||||||
|
, "empty emphasis" =: emph mempty =?> "<em></em>"
|
||||||
|
, "empty strong" =: strong mempty =?> "<strong></strong>"
|
||||||
|
, "empty strong emphasis" =: strong (emph mempty) =?> "**<em></em>**"
|
||||||
|
, "empty emphasized strong" =: emph (strong mempty) =?> "*<strong></strong>*"
|
||||||
|
, "strong" =: strong (text "foo") =?> "**foo**"
|
||||||
|
, "strong inside word" =: text "foo" <> strong (text "bar") <> text "baz" =?> "foo<strong>bar</strong>baz"
|
||||||
|
, "strong emphasis" =: strong (emph (text "foo")) =?> "***foo***"
|
||||||
|
, "strong after emphasis" =: emph (text "foo") <> strong (text "bar") =?> "*foo*<strong>bar</strong>"
|
||||||
|
, "strong emphasis after emphasis" =: emph (text "foo") <> strong (emph (text "bar")) =?> "*foo*<strong>*bar*</strong>"
|
||||||
|
, "strong in the end of emphasis" =: emph (text "foo" <> strong (text "bar")) =?> "*foo<strong>bar</strong>*"
|
||||||
, "strikeout" =: strikeout (text "foo") =?> "<del>foo</del>"
|
, "strikeout" =: strikeout (text "foo") =?> "<del>foo</del>"
|
||||||
|
, "space at the beginning of emphasis" =: emph (text " foo") =?> "<em> foo</em>"
|
||||||
|
, "space at the end of emphasis" =: emph (text "foo ") =?> "<em>foo </em>"
|
||||||
|
, "space at the beginning of strong" =: strong (text " foo") =?> "<strong> foo</strong>"
|
||||||
|
, "space at the end of strong" =: strong (text "foo ") =?> "<strong>foo </strong>"
|
||||||
|
, "space at the beginning of strong emphasis" =: strong (emph (text " foo")) =?> "**<em> foo</em>**"
|
||||||
|
, "space at the end of strong emphasis" =: strong (emph (text "foo ")) =?> "**<em>foo </em>**"
|
||||||
|
, "space at the beginning of emphasiszed strong" =: emph (strong (text " foo")) =?> "*<strong> foo</strong>*"
|
||||||
|
, "space at the end of emphasized strong" =: emph (strong (text "foo ")) =?> "*<strong>foo </strong>*"
|
||||||
]
|
]
|
||||||
, "superscript" =: superscript (text "foo") =?> "<sup>foo</sup>"
|
, "superscript" =: superscript (text "foo") =?> "<sup>foo</sup>"
|
||||||
, "subscript" =: subscript (text "foo") =?> "<sub>foo</sub>"
|
, "subscript" =: subscript (text "foo") =?> "<sub>foo</sub>"
|
||||||
, "smallcaps" =: smallcaps (text "foo") =?> "<em>foo</em>"
|
, "smallcaps" =: smallcaps (text "foo") =?> "*foo*"
|
||||||
, "smallcaps near emphasis" =: emph (str "foo") <> smallcaps (str "bar") =?> "<em>foobar</em>"
|
, "smallcaps near emphasis" =: emph (str "foo") <> smallcaps (str "bar") =?> "*foobar*"
|
||||||
, "single quoted" =: singleQuoted (text "foo") =?> "‘foo’"
|
, "single quoted" =: singleQuoted (text "foo") =?> "‘foo’"
|
||||||
, "double quoted" =: doubleQuoted (text "foo") =?> "“foo”"
|
, "double quoted" =: doubleQuoted (text "foo") =?> "“foo”"
|
||||||
-- Cite is trivial
|
-- Cite is trivial
|
||||||
, testGroup "code"
|
, testGroup "code"
|
||||||
[ "simple" =: code "foo" =?> "<code>foo</code>"
|
[ "simple" =: code "foo" =?> "=foo="
|
||||||
|
, "empty" =: code "" =?> "<code></code>"
|
||||||
|
, "space" =: code " " =?> "<code> </code>"
|
||||||
|
, "space at the beginning" =: code " foo" =?> "<code> foo</code>"
|
||||||
|
, "space at the end" =: code "foo " =?> "<code>foo </code>"
|
||||||
|
, "use tags for =" =: code "foo = bar" =?> "<code>foo = bar</code>"
|
||||||
, "escape tag" =: code "<code>foo = bar</code> baz" =?> "<code><code>foo = bar<</code><code>/code> baz</code>"
|
, "escape tag" =: code "<code>foo = bar</code> baz" =?> "<code><code>foo = bar<</code><code>/code> baz</code>"
|
||||||
, "normalization with attributes" =: codeWith ("",["haskell"],[]) "foo" <> code "bar" =?> "<code>foobar</code>"
|
, "normalization with attributes" =: codeWith ("",["haskell"],[]) "foo" <> code "bar" =?> "=foobar="
|
||||||
, "normalization" =: code "</co" <> code "de>" =?> "<code><</code><code>/code></code>"
|
, "code tag" =: code "<code>foo</code>" =?> "=<code>foo</code>="
|
||||||
, "normalization with empty string" =: code "</co" <> str "" <> code "de>" =?> "<code><</code><code>/code></code>"
|
, "normalization" =: code "</co" <> code "de>" <> code "=" =?> "<code><</code><code>/code>=</code>"
|
||||||
|
, "normalization with empty string" =: code "</co" <> str "" <> code "de>" <> code "=" =?> "<code><</code><code>/code>=</code>"
|
||||||
|
, "emphasized code" =: emph (code "foo") =?> "*=foo=*"
|
||||||
|
, "strong code" =: strong (code "foo") =?> "**=foo=**"
|
||||||
]
|
]
|
||||||
, testGroup "spaces"
|
, testGroup "spaces"
|
||||||
[ "space" =: text "a" <> space <> text "b" =?> "a b"
|
[ "space" =: text "a" <> space <> text "b" =?> "a b"
|
||||||
|
@ -385,7 +413,7 @@ tests = [ testGroup "block elements"
|
||||||
, testGroup "math"
|
, testGroup "math"
|
||||||
[ "inline math" =: math "2^3" =?> "2<sup>3</sup>"
|
[ "inline math" =: math "2^3" =?> "2<sup>3</sup>"
|
||||||
, "display math" =: displayMath "2^3" =?> "2<sup>3</sup>"
|
, "display math" =: displayMath "2^3" =?> "2<sup>3</sup>"
|
||||||
, "multiple letters in inline math" =: math "abc" =?> "<em>abc</em>"
|
, "multiple letters in inline math" =: math "abc" =?> "*abc*"
|
||||||
, "expand math before normalization" =: math "[" <> str "2]" =?> "<verbatim>[2]</verbatim>"
|
, "expand math before normalization" =: math "[" <> str "2]" =?> "<verbatim>[2]</verbatim>"
|
||||||
, "multiple math expressions inside one inline list" =: math "5_4" <> text ", " <> displayMath "3^2" =?> "5<sub>4</sub>, 3<sup>2</sup>"
|
, "multiple math expressions inside one inline list" =: math "5_4" <> text ", " <> displayMath "3^2" =?> "5<sub>4</sub>, 3<sup>2</sup>"
|
||||||
]
|
]
|
||||||
|
@ -461,7 +489,7 @@ tests = [ testGroup "block elements"
|
||||||
"<em>foo</em>bar"
|
"<em>foo</em>bar"
|
||||||
, "emph quoted" =:
|
, "emph quoted" =:
|
||||||
para (doubleQuoted (emph (text "foo"))) =?>
|
para (doubleQuoted (emph (text "foo"))) =?>
|
||||||
"“<em>foo</em>”"
|
"“*foo*”"
|
||||||
, "strong word before" =:
|
, "strong word before" =:
|
||||||
para (text "foo" <> strong (text "bar")) =?>
|
para (text "foo" <> strong (text "bar")) =?>
|
||||||
"foo<strong>bar</strong>"
|
"foo<strong>bar</strong>"
|
||||||
|
@ -470,7 +498,7 @@ tests = [ testGroup "block elements"
|
||||||
"<strong>foo</strong>bar"
|
"<strong>foo</strong>bar"
|
||||||
, "strong quoted" =:
|
, "strong quoted" =:
|
||||||
para (singleQuoted (strong (text "foo"))) =?>
|
para (singleQuoted (strong (text "foo"))) =?>
|
||||||
"‘<strong>foo</strong>’"
|
"‘**foo**’"
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
|
@ -11,7 +11,7 @@ markdown test suite.
|
||||||
|
|
||||||
** Level 2 with an [[/url][embedded link]]
|
** Level 2 with an [[/url][embedded link]]
|
||||||
|
|
||||||
*** Level 3 with <em>emphasis</em>
|
*** Level 3 with *emphasis*
|
||||||
|
|
||||||
**** Level 4
|
**** Level 4
|
||||||
|
|
||||||
|
@ -19,7 +19,7 @@ markdown test suite.
|
||||||
|
|
||||||
* Level 1
|
* Level 1
|
||||||
|
|
||||||
** Level 2 with <em>emphasis</em>
|
** Level 2 with *emphasis*
|
||||||
|
|
||||||
*** Level 3
|
*** Level 3
|
||||||
|
|
||||||
|
@ -271,18 +271,18 @@ Loose:
|
||||||
|
|
||||||
Multiple blocks with italics:
|
Multiple blocks with italics:
|
||||||
|
|
||||||
<em>apple</em> :: red fruit
|
*apple* :: red fruit
|
||||||
|
|
||||||
contains seeds, crisp, pleasant to taste
|
contains seeds, crisp, pleasant to taste
|
||||||
<em>orange</em> :: orange fruit
|
*orange* :: orange fruit
|
||||||
|
|
||||||
<example>
|
<example>
|
||||||
{ orange code block }
|
{ orange code block }
|
||||||
</example>
|
</example>
|
||||||
|
|
||||||
<quote>
|
<quote>
|
||||||
orange block quote
|
orange block quote
|
||||||
</quote>
|
</quote>
|
||||||
|
|
||||||
Multiple definitions, tight:
|
Multiple definitions, tight:
|
||||||
|
|
||||||
|
@ -331,7 +331,7 @@ Interpreted markdown in a table:
|
||||||
<td>
|
<td>
|
||||||
</literal>
|
</literal>
|
||||||
|
|
||||||
This is <em>emphasized</em>
|
This is *emphasized*
|
||||||
|
|
||||||
<literal style="html">
|
<literal style="html">
|
||||||
</td>
|
</td>
|
||||||
|
@ -341,7 +341,7 @@ This is <em>emphasized</em>
|
||||||
<td>
|
<td>
|
||||||
</literal>
|
</literal>
|
||||||
|
|
||||||
And this is <strong>strong</strong>
|
And this is **strong**
|
||||||
|
|
||||||
<literal style="html">
|
<literal style="html">
|
||||||
</td>
|
</td>
|
||||||
|
@ -461,27 +461,25 @@ Hr’s:
|
||||||
|
|
||||||
* Inline Markup
|
* Inline Markup
|
||||||
|
|
||||||
This is <em>emphasized</em>, and so <em>is this</em>.
|
This is *emphasized*, and so *is this*.
|
||||||
|
|
||||||
This is <strong>strong</strong>, and so <strong>is this</strong>.
|
This is **strong**, and so **is this**.
|
||||||
|
|
||||||
An <em>[[/url][emphasized link]]</em>.
|
An *[[/url][emphasized link]]*.
|
||||||
|
|
||||||
<strong><em>This is strong and em.</em></strong>
|
***This is strong and em.***
|
||||||
|
|
||||||
So is <strong><em>this</em></strong> word.
|
So is ***this*** word.
|
||||||
|
|
||||||
<strong><em>This is strong and em.</em></strong>
|
***This is strong and em.***
|
||||||
|
|
||||||
So is <strong><em>this</em></strong> word.
|
So is ***this*** word.
|
||||||
|
|
||||||
This is code: <code>></code>, <code>$</code>, <code>\</code>, <code>\$</code>,
|
This is code: =>=, =$=, =\=, =\$=, =<html>=.
|
||||||
<code><html></code>.
|
|
||||||
|
|
||||||
<del>This is <em>strikeout</em>.</del>
|
<del>This is *strikeout*.</del>
|
||||||
|
|
||||||
Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup>
|
Superscripts: a<sup>bc</sup>d a<sup>*hello*</sup> a<sup>hello there</sup>.
|
||||||
a<sup>hello there</sup>.
|
|
||||||
|
|
||||||
Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O.
|
Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O.
|
||||||
|
|
||||||
|
@ -500,8 +498,8 @@ spaces: a^b c^d, a~b c~d.
|
||||||
|
|
||||||
‘He said, “I want to go.”’ Were you alive in the 70’s?
|
‘He said, “I want to go.”’ Were you alive in the 70’s?
|
||||||
|
|
||||||
Here is some quoted ‘<code>code</code>’ and a
|
Here is some quoted ‘=code=’ and a “[[http://example.com/?foo=1&bar=2][quoted
|
||||||
“[[http://example.com/?foo=1&bar=2][quoted link]]”.
|
link]]”.
|
||||||
|
|
||||||
Some dashes: one—two — three—four — five.
|
Some dashes: one—two — three—four — five.
|
||||||
|
|
||||||
|
@ -515,22 +513,21 @@ Ellipses…and…and….
|
||||||
|
|
||||||
- <literal style="tex">\cite[22-23]{smith.1899}</literal>
|
- <literal style="tex">\cite[22-23]{smith.1899}</literal>
|
||||||
- <verbatim>2 + 2 = 4</verbatim>
|
- <verbatim>2 + 2 = 4</verbatim>
|
||||||
- <em>x</em> ∈ <em>y</em>
|
- *x* ∈ *y*
|
||||||
- <em>α</em> ∧ <em>ω</em>
|
- *α* ∧ *ω*
|
||||||
- 223
|
- 223
|
||||||
- <em>p</em>-Tree
|
- *p*-Tree
|
||||||
- Here’s some display math:
|
- Here’s some display math:
|
||||||
<verbatim>$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</verbatim>
|
<verbatim>$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</verbatim>
|
||||||
- Here’s one that has a line break in it:
|
- Here’s one that has a line break in it: *α* + *ω* × *x*<sup>2</sup>.
|
||||||
<em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup>.
|
|
||||||
|
|
||||||
These shouldn’t be math:
|
These shouldn’t be math:
|
||||||
|
|
||||||
- To get the famous equation, write <code>$e = mc^2$</code>.
|
- To get the famous equation, write <code>$e = mc^2$</code>.
|
||||||
- $22,000 is a <em>lot</em> of money. So is $34,000. (It worked if “lot” is
|
- $22,000 is a *lot* of money. So is $34,000. (It worked if “lot” is
|
||||||
emphasized.)
|
emphasized.)
|
||||||
- Shoes ($20) and socks ($5).
|
- Shoes ($20) and socks ($5).
|
||||||
- Escaped <code>$</code>: $73 <em>this should be emphasized</em> 23$.
|
- Escaped =$=: $73 *this should be emphasized* 23$.
|
||||||
|
|
||||||
Here’s a LaTeX table:
|
Here’s a LaTeX table:
|
||||||
|
|
||||||
|
@ -669,7 +666,7 @@ An e-mail address: [[mailto:nobody@nowhere.net][nobody@nowhere.net]]
|
||||||
Blockquoted: [[http://example.com/]]
|
Blockquoted: [[http://example.com/]]
|
||||||
</quote>
|
</quote>
|
||||||
|
|
||||||
Auto-links should not occur here: <code><http://example.com/></code>
|
Auto-links should not occur here: =<http://example.com/>=
|
||||||
|
|
||||||
<example>
|
<example>
|
||||||
or here: <http://example.com/>
|
or here: <http://example.com/>
|
||||||
|
@ -689,7 +686,7 @@ Here is a movie [[movie.jpg][movie]] icon.
|
||||||
|
|
||||||
* Footnotes
|
* Footnotes
|
||||||
|
|
||||||
Here is a footnote reference,[1] and another.[2] This should <em>not</em> be a
|
Here is a footnote reference,[1] and another.[2] This should *not* be a
|
||||||
footnote reference, because it contains a space.[^my note] Here is an inline
|
footnote reference, because it contains a space.[^my note] Here is an inline
|
||||||
note.[3]
|
note.[3]
|
||||||
|
|
||||||
|
@ -716,9 +713,9 @@ This paragraph should not be part of the note, as it is not indented.
|
||||||
If you want, you can indent every line, but you can also be lazy and just
|
If you want, you can indent every line, but you can also be lazy and just
|
||||||
indent the first line of each block.
|
indent the first line of each block.
|
||||||
|
|
||||||
[3] This is <em>easier</em> to type. Inline notes may contain
|
[3] This is *easier* to type. Inline notes may contain
|
||||||
[[http://google.com][links]] and <code>]</code> verbatim characters, as
|
[[http://google.com][links]] and =]= verbatim characters, as well as
|
||||||
well as [bracketed text].
|
[bracketed text].
|
||||||
|
|
||||||
[4] In quote.
|
[4] In quote.
|
||||||
|
|
||||||
|
|
Loading…
Add table
Reference in a new issue