diff --git a/MANUAL.txt b/MANUAL.txt index 88f0b681cd0b..8f9ba8b0e5bd 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -301,6 +301,12 @@ header when requesting a document from a URL: - `asciidoc` (modern [AsciiDoc] as interpreted by [AsciiDoctor]) - `asciidoc_legacy` ([AsciiDoc] as interpreted by [`asciidoc-py`]). - `asciidoctor` (deprecated synonym for `asciidoc`) + - `bbcode` [BBCode] + - `bbcode_fluxbb` [BBCode (FluxBB)] + - `bbcode_phpbb` [BBCode (phpBB)] + - `bbcode_steam` [BBCode (Hubzilla)] + - `bbcode_hubzilla` [BBCode (Hubzilla)] + - `bbcode_xenforo` [BBCode (xenForo)] - `beamer` ([LaTeX beamer][`beamer`] slide show) - `bibtex` ([BibTeX] bibliography) - `biblatex` ([BibLaTeX] bibliography) @@ -546,6 +552,12 @@ header when requesting a document from a URL: [EndNote XML bibliography]: https://support.clarivate.com/Endnote/s/article/EndNote-XML-Document-Type-Definition [typst]: https://typst.app [mdoc]: https://mandoc.bsd.lv/man/mdoc.7.html +[BBCode]: https://www.bbcode.org/reference.php +[BBCode (FluxBB)]: https://web.archive.org/web/20210623155046/https://fluxbb.org/forums/help.php#bbcode +[BBCode (Hubzilla)]: https://hubzilla.org/help/member/bbcode +[BBCode (Steam)]: https://steamcommunity.com/comment/ForumTopic/formattinghelp +[BBCode (phpBB)]: https://www.phpbb.com/community/help/bbcode +[BBCode (xenForo)]: https://www.xenfocus.com/community/help/bb-codes/ ## Reader options {.options} diff --git a/data/templates/default.bbcode b/data/templates/default.bbcode new file mode 100644 index 000000000000..36d66c2760f2 --- /dev/null +++ b/data/templates/default.bbcode @@ -0,0 +1 @@ +$body$ diff --git a/pandoc.cabal b/pandoc.cabal index e9d3fec2ebb8..a5f21dbb26e3 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -111,6 +111,7 @@ data-files: data/templates/font-settings.latex data/templates/after-header-includes.latex data/templates/default.vimdoc + data/templates/default.bbcode -- translations data/translations/*.yaml @@ -342,6 +343,7 @@ extra-source-files: test/tables.fb2 test/tables.muse test/tables.vimdoc + test/tables.bbcode test/tables.xwiki test/tables/*.html4 test/tables/*.html5 @@ -389,6 +391,7 @@ extra-source-files: test/writer.xwiki test/writer.muse test/writer.vimdoc + test/writer.bbcode test/ansi-test.ansi test/writers-lang-and-dir.latex test/writers-lang-and-dir.context @@ -666,6 +669,7 @@ library Text.Pandoc.Writers.BibTeX, Text.Pandoc.Writers.ANSI, Text.Pandoc.Writers.Vimdoc, + Text.Pandoc.Writers.BBCode, Text.Pandoc.PDF, Text.Pandoc.UTF8, Text.Pandoc.Scripting, @@ -881,6 +885,7 @@ test-suite test-pandoc Tests.Writers.OOXML Tests.Writers.Ms Tests.Writers.AnnotatedTable + Tests.Writers.BBCode benchmark benchmark-pandoc import: common-executable diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index ab517fc1b88d..047798e686ee 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -121,6 +121,11 @@ getDefaultTemplate format = do "markdown_phpextra" -> getDefaultTemplate "markdown" "gfm" -> getDefaultTemplate "commonmark" "commonmark_x" -> getDefaultTemplate "commonmark" + "bbcode_phpbb" -> getDefaultTemplate "bbcode" + "bbcode_fluxbb" -> getDefaultTemplate "bbcode" + "bbcode_steam" -> getDefaultTemplate "bbcode" + "bbcode_hubzilla" -> getDefaultTemplate "bbcode" + "bbcode_xenforo" -> getDefaultTemplate "bbcode" _ -> do let fname = "templates" "default" <.> T.unpack format readDataFile fname >>= toTextM fname diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs index 556ff5ddfec8..e74ea4f00353 100644 --- a/src/Text/Pandoc/Writers.hs +++ b/src/Text/Pandoc/Writers.hs @@ -80,6 +80,12 @@ module Text.Pandoc.Writers , writeXWiki , writeZimWiki , writeVimdoc + , writeBBCode + , writeBBCodeSteam + , writeBBCodeFluxBB + , writeBBCodePhpBB + , writeBBCodeHubzilla + , writeBBCodeXenforo , getWriter ) where @@ -134,6 +140,14 @@ import Text.Pandoc.Writers.XML import Text.Pandoc.Writers.XWiki import Text.Pandoc.Writers.ZimWiki import Text.Pandoc.Writers.Vimdoc +import Text.Pandoc.Writers.BBCode ( + writeBBCode, + writeBBCodeFluxBB, + writeBBCodeHubzilla, + writeBBCodePhpBB, + writeBBCodeSteam, + writeBBCodeXenforo, + ) data Writer m = TextWriter (WriterOptions -> Pandoc -> m Text) | ByteStringWriter (WriterOptions -> Pandoc -> m BL.ByteString) @@ -209,6 +223,12 @@ writers = [ ,("ansi" , TextWriter writeANSI) ,("xml" , TextWriter writeXML) ,("vimdoc" , TextWriter writeVimdoc) + ,("bbcode" , TextWriter writeBBCode) + ,("bbcode_steam" , TextWriter writeBBCodeSteam) + ,("bbcode_phpbb" , TextWriter writeBBCodePhpBB) + ,("bbcode_fluxbb", TextWriter writeBBCodeFluxBB) + ,("bbcode_hubzilla" , TextWriter writeBBCodeHubzilla) + ,("bbcode_xenforo" , TextWriter writeBBCodeXenforo) ] -- | Retrieve writer, extensions based on formatSpec (format+extensions). diff --git a/src/Text/Pandoc/Writers/BBCode.hs b/src/Text/Pandoc/Writers/BBCode.hs new file mode 100644 index 000000000000..213b475e6b79 --- /dev/null +++ b/src/Text/Pandoc/Writers/BBCode.hs @@ -0,0 +1,1089 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE Strict #-} +{-# LANGUAGE TypeApplications #-} +{- | + Module : Text.Pandoc.Writers.BBCode + Copyright : © 2025 Aleksey Myshko + License : GNU GPL, version 2 or above + + Maintainer : Aleksey Myshko + Stability : alpha + Portability : portable + +Conversion of 'Pandoc' documents to various BBCode flavors. +-} + +module Text.Pandoc.Writers.BBCode ( + -- * Predefined writers + -- Writers for different flavors of BBCode. 'writeBBCode' is a synonym for + -- 'writeBBCode_official' + writeBBCode, + writeBBCodeOfficial, + writeBBCodeSteam, + writeBBCodePhpBB, + writeBBCodeFluxBB, + writeBBCodeHubzilla, + writeBBCodeXenforo, + + -- * Extending the writer + -- $extending + FlavorSpec (..), + WriterState (..), + RR, + writeBBCodeCustom, + inlineToBBCode, + inlineListToBBCode, + blockToBBCode, + blockListToBBCode, + + -- ** Handling attributes + -- $wrapping_spans_divs + attrToMap, + + -- * Predefined flavor specifications + officialSpec, + steamSpec, + phpbbSpec, + fluxbbSpec, + hubzillaSpec, + xenforoSpec, +) where + +import Control.Applicative (some) +import Control.Monad (forM) +import Control.Monad.Reader (MonadReader (..), ReaderT (..), asks) +import Control.Monad.State (MonadState (..), StateT, evalStateT, gets, modify) +import Data.Default (Default (..)) +import Data.Either (isRight) +import Data.Foldable (toList) +import Data.Map.Strict (Map) +import qualified Data.Map.Strict as Map +import Data.Maybe (fromMaybe, isJust) +import Data.Sequence (Seq, (|>)) +import qualified Data.Sequence as Seq +import Data.Text (Text) +import qualified Data.Text as T +import Text.DocLayout hiding (char, link, text) +import Text.Pandoc.Class.PandocMonad (PandocMonad, report) +import Text.Pandoc.Definition +import Text.Pandoc.Logging (LogMessage (..)) +import Text.Pandoc.Options (WriterOptions (..)) +import Text.Pandoc.Parsing (char, digit, eof, readWith) +import Text.Pandoc.Shared (inquotes, onlySimpleTableCells, removeFormatting, trim, tshow) +import Text.Pandoc.Templates (renderTemplate) +import Text.Pandoc.URI (escapeURI) +import Text.Pandoc.Writers.Shared (defField, metaToContext, toLegacyTable, unsmartify) +import Text.Read (readMaybe) + +-- Type synonym to prevent haddock-generated HTML from overflowing +type PandocTable = + (Attr, Caption, [ColSpec], TableHead, [TableBody], TableFoot) + +-- $extending +-- If you want to support more Pandoc elements (or render some of them +-- differently) you can do so by creating your own 'FlavorSpec' +-- +-- The module exports the @'FlavorSpec'@s underlying @writeBBCode_*@ functions, +-- namely 'officialSpec', 'steamSpec', 'phpbbSpec', 'fluxbbSpec', +-- 'hubzillaSpec'. +-- +-- You can create and use your own renderers, for instance here we define a +-- renderer for 'CodeBlock' and use it to create a derivative format: +-- +-- > renderCodeBlockCustom :: (PandocMonad m) => Attr -> Text -> RR m (Doc Text) +-- > renderCodeBlockCustom (_, cls, _) code = do +-- > let opening = case cls of +-- > (lang : _) -> "[code=" <> lang <> "]" +-- > ("c++" : _) -> "[code=cpp]" +-- > _ -> "[code]" +-- > pure $ mconcat [literal opening, literal code, cr, "[/code]"] +-- > +-- > specCustom = officialSpec{renderCodeBlock = renderCodeBlockCustom} +-- +-- Then we can use it to render 'Pandoc' document via 'writeBBCode_custom' + +{- | Data type that is a collection of renderers for most elements in a Pandoc +AST (see 'Block' and 'Inline') + +The intention here is to allow inheritance between formats, for instance if +format A and format @B@ differ only in rendering tables, @B@ can be implemented +as @A{'renderTable' = renderTableB}@ +-} +data FlavorSpec = FlavorSpec + { renderBlockQuote :: + forall m. + (PandocMonad m) => + [Block] -> + RR m (Doc Text) + -- ^ Render 'BlockQuote' + , renderBulletList :: + forall m. + (PandocMonad m) => + [[Block]] -> + RR m (Doc Text) + -- ^ Render 'BulletList' + , renderCodeBlock :: + forall m. + (PandocMonad m) => + Attr -> + Text -> + RR m (Doc Text) + -- ^ Render 'CodeBlock' + , renderDefinitionList :: + forall m. + (PandocMonad m) => + [([Inline], [[Block]])] -> + RR m (Doc Text) + -- ^ Render 'DefinitionList' + , renderHeader :: + forall m. + (PandocMonad m) => + Int -> + Attr -> + [Inline] -> + RR m (Doc Text) + -- ^ Render 'Header' + , renderInlineCode :: + forall m. + (PandocMonad m) => + Attr -> + Text -> + RR m (Doc Text) + -- ^ Render 'Code' + , renderLink :: + forall m. + (PandocMonad m) => + Attr -> + [Inline] -> + Target -> + RR m (Doc Text) + -- ^ Render 'Link' + , renderOrderedList :: + forall m. + (PandocMonad m) => + ListAttributes -> + [[Block]] -> + RR m (Doc Text) + -- ^ Render 'OrderedList' + , renderStrikeout :: + forall m. + (PandocMonad m) => + [Inline] -> + RR m (Doc Text) + -- ^ Render 'Strikeout' + , renderTable :: forall m. (PandocMonad m) => PandocTable -> RR m (Doc Text) + -- ^ Render 'Table' + , renderHorizontalRule :: + forall m. + (PandocMonad m) => + RR m (Doc Text) + -- ^ Render 'HorizontalRule' + , renderLineBlock :: + forall m. + (PandocMonad m) => + [[Inline]] -> + RR m (Doc Text) + -- ^ Render 'LineBlock' + , renderPara :: + forall m. + (PandocMonad m) => + [Inline] -> + RR m (Doc Text) + -- ^ Render 'Para' + , renderSuperscript :: + forall m. + (PandocMonad m) => + [Inline] -> + RR m (Doc Text) + -- ^ Render 'Superscript' + , renderSubscript :: forall m. (PandocMonad m) => [Inline] -> RR m (Doc Text) + -- ^ Render 'Subscript' + , renderSmallCaps :: forall m. (PandocMonad m) => [Inline] -> RR m (Doc Text) + -- ^ Render 'SmallCaps' + , renderCite :: + forall m. + (PandocMonad m) => + [Citation] -> + [Inline] -> + RR m (Doc Text) + -- ^ Render 'Cite' + , renderNote :: forall m. (PandocMonad m) => [Block] -> RR m (Doc Text) + -- ^ Render 'Note' + , renderFigure :: + forall m. + (PandocMonad m) => + Attr -> + Caption -> + [Block] -> + RR m (Doc Text) + -- ^ Render 'Figure' + , renderQuoted :: + forall m. + (PandocMonad m) => + QuoteType -> + [Inline] -> + RR m (Doc Text) + -- ^ Render 'Quoted' + , renderMath :: + forall m. + (PandocMonad m) => + MathType -> + Text -> + RR m (Doc Text) + -- ^ Render 'Math' + , renderImage :: + forall m. + (PandocMonad m) => + Attr -> + [Inline] -> + Target -> + RR m (Doc Text) + -- ^ Render 'Image' + , wrapSpanDiv :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text + -- ^ Wrap document in bbcode tags based on attributes/classes. Boolean flag + -- indicates whether passed argument is a Div or a Span (True means Div) + } + +data WriterState = WriterState + { writerOptions :: WriterOptions + , flavorSpec :: FlavorSpec + , inList :: Bool + } + +instance Default WriterState where + def = + WriterState + { writerOptions = def + , flavorSpec = officialSpec + , inList = False + } + +-- | The base of a renderer monad. +type RR m a = StateT (Seq (Doc Text)) (ReaderT WriterState m) a + +pandocToBBCode :: (PandocMonad m) => Pandoc -> RR m Text +pandocToBBCode (Pandoc meta body) = do + opts <- asks writerOptions + -- Run the rendering that mutates the state by producing footnotes + bodyContents <- blockListToBBCode body + -- Get the footnotes + footnotes <- get + -- Separate footnotes (if any) with a horizontal rule + footnotesSep <- + if null footnotes + then pure empty + else + (\hr -> blankline <> hr <> blankline) + <$> blockToBBCode HorizontalRule + -- Put footnotes after the main text + let docText = bodyContents <> footnotesSep <> vsep (toList footnotes) + metadata <- metaToContext opts blockListToBBCode inlineListToBBCode meta + let context = defField "body" docText metadata + case writerTemplate opts of + Just tpl -> pure $ render Nothing (renderTemplate tpl context) + Nothing -> pure $ render Nothing docText + +writeBBCode + , writeBBCodeOfficial + , writeBBCodeSteam + , writeBBCodePhpBB + , writeBBCodeFluxBB + , writeBBCodeHubzilla + , writeBBCodeXenforo :: + (PandocMonad m) => WriterOptions -> Pandoc -> m Text +writeBBCode = writeBBCodeOfficial +writeBBCodeOfficial = writeBBCodeCustom officialSpec +writeBBCodeSteam = writeBBCodeCustom steamSpec +writeBBCodePhpBB = writeBBCodeCustom phpbbSpec +writeBBCodeFluxBB = writeBBCodeCustom fluxbbSpec +writeBBCodeHubzilla = writeBBCodeCustom hubzillaSpec +writeBBCodeXenforo = writeBBCodeCustom xenforoSpec + +{- | Convert a 'Pandoc' document to BBCode using the given 'FlavorSpec' and +'WriterOptions'. +-} +writeBBCodeCustom :: + (PandocMonad m) => FlavorSpec -> WriterOptions -> Pandoc -> m Text +writeBBCodeCustom spec opts document = + runRR mempty def{writerOptions = opts, flavorSpec = spec} $ + pandocToBBCode document + where + runRR :: (Monad m) => Seq (Doc Text) -> WriterState -> RR m a -> m a + runRR footnotes writerState action = + runReaderT (evalStateT action footnotes) writerState + +blockListToBBCode :: (PandocMonad m) => [Block] -> RR m (Doc Text) +blockListToBBCode blocks = + chomp . vsep . filter (not . null) + <$> mapM blockToBBCode blocks + +blockToBBCode :: (PandocMonad m) => Block -> RR m (Doc Text) +blockToBBCode block = do + spec <- asks flavorSpec + case block of + Plain inlines -> inlineListToBBCode inlines + Para inlines -> renderPara spec inlines + LineBlock inliness -> renderLineBlock spec inliness + CodeBlock attr code -> renderCodeBlock spec attr code + RawBlock format raw -> case format of + "bbcode" -> pure $ literal raw + _ -> "" <$ report (BlockNotRendered block) + BlockQuote blocks -> renderBlockQuote spec blocks + OrderedList attr items -> renderOrderedList spec attr items + BulletList items -> renderBulletList spec items + DefinitionList items -> renderDefinitionList spec items + Header level attr inlines -> renderHeader spec level attr inlines + HorizontalRule -> renderHorizontalRule spec + Table attr blkCapt specs thead tbody tfoot -> + renderTable spec (attr, blkCapt, specs, thead, tbody, tfoot) + Figure attr caption blocks -> renderFigure spec attr caption blocks + Div attr blocks -> do + contents <- blockListToBBCode blocks + let kvcMap = attrToMap attr + -- whether passed contents is a Div (Block) element + -- vvvv + pure $ wrapSpanDiv spec True kvcMap contents + +inlineToBBCode :: (PandocMonad m) => Inline -> RR m (Doc Text) +inlineToBBCode inline = do + spec <- asks flavorSpec + case inline of + Str str -> do + opts <- asks writerOptions + pure . literal $ unsmartify opts str + Emph inlines -> do + contents <- inlineListToBBCode inlines + pure $ mconcat ["[i]", contents, "[/i]"] + Underline inlines -> do + contents <- inlineListToBBCode inlines + pure $ mconcat ["[u]", contents, "[/u]"] + Strong inlines -> do + contents <- inlineListToBBCode inlines + pure $ mconcat ["[b]", contents, "[/b]"] + Strikeout inlines -> renderStrikeout spec inlines + Superscript inlines -> renderSuperscript spec inlines + Subscript inlines -> renderSubscript spec inlines + SmallCaps inlines -> renderSmallCaps spec inlines + Quoted typ inlines -> renderQuoted spec typ inlines + Cite cits inlines -> renderCite spec cits inlines + Code attr code -> renderInlineCode spec attr code + Space -> pure space + SoftBreak -> pure space + LineBreak -> pure cr + Math typ math -> renderMath spec typ math + RawInline (Format format) text -> case format of + "bbcode" -> pure $ literal text + _ -> "" <$ report (InlineNotRendered inline) + Link attr txt target -> renderLink spec attr txt target + Image attr alt target -> renderImage spec attr alt target + Note blocks -> renderNote spec blocks + Span attr inlines -> do + contents <- inlineListToBBCode inlines + let kvcMap = attrToMap attr + -- whether passed contents is a Div (Block element) + -- vvvvv + pure $ wrapSpanDiv spec False kvcMap contents + +renderImageDefault :: + (PandocMonad m) => Attr -> [Inline] -> Target -> RR m (Doc Text) +renderImageDefault (_, _, kvList) alt (source, title) = do + altText <- + trim . render Nothing + <$> inlineListToBBCode (removeFormatting alt) + let kvMap = Map.fromList kvList + -- No BBCode flavor supported by the Writer has local images support, but we + -- still allow source to be plain path or anything else + pure . literal $ + mconcat + [ "[img" + , if T.null altText + then "" + else " alt=" <> inquotes altText + , if T.null title + then "" + else " title=" <> inquotes title + , case Map.lookup "width" kvMap of + Just w + | isJust (readMaybe @Int $ T.unpack w) -> + " width=" <> inquotes w + _ -> "" + , case Map.lookup "height" kvMap of + Just h + | isJust (readMaybe @Int $ T.unpack h) -> + " height=" <> inquotes h + _ -> "" + , "]" + , source + , "[/img]" + ] + +renderImageOmit :: + (PandocMonad m) => Attr -> [Inline] -> Target -> RR m (Doc Text) +renderImageOmit _ _ _ = pure "" + +{- | Basic phpBB doesn't support any attributes, although +@[img src=https://example.com]whatever[/img]@ is supported, but text in tag has +no effect +-} +renderImagePhpBB :: + (PandocMonad m) => Attr -> [Inline] -> Target -> RR m (Doc Text) +renderImagePhpBB _ _ (source, _) = + pure . literal $ mconcat ["[img]", source, "[/img]"] + +renderImageXenforo :: + (PandocMonad m) => Attr -> [Inline] -> Target -> RR m (Doc Text) +renderImageXenforo (_, _, kvList) alt (source, title) = do + altText <- + trim . render Nothing + <$> inlineListToBBCode (removeFormatting alt) + let kvMap = Map.fromList kvList + -- No BBCode flavor supported by the Writer has local images support, but we + -- still allow source to be plain path or anything else + pure . literal $ + mconcat + [ "[img" + , if T.null altText + then "" + else " alt=" <> inquotes altText + , if T.null title + then "" + else " title=" <> inquotes title + , case Map.lookup "width" kvMap of + Just w + | isRight (readWith sizeP Nothing w) -> + " width=" <> w + _ -> "" + , "]" + , source + , "[/img]" + ] + where + sizeP = some digit >> char '%' >> eof + +{- | Check whether character is a bracket + +>>> T.filter notBracket "[a]b[[ó]qü]]n®" +"ab\243q\252n\174" +-} +notBracket :: Char -> Bool +notBracket = \case + '[' -> False + ']' -> False + _ -> True + +-- FluxBB uses [img=alt text] instead of [img alt="alt text"] +renderImageFluxBB :: + (PandocMonad m) => Attr -> [Inline] -> Target -> RR m (Doc Text) +renderImageFluxBB _ alt (source, _) = do + alt' <- T.filter notBracket . render Nothing <$> inlineListToBBCode alt + pure . literal $ + mconcat + [ "[img" + , if T.null alt' + then "" + else "=" <> alt' + , "]" + , source + , "[/img]" + ] + +inlineListToBBCode :: (PandocMonad m) => [Inline] -> RR m (Doc Text) +inlineListToBBCode inlines = mconcat <$> mapM inlineToBBCode inlines + +-- Taken from Data.Ord +clamp :: (Ord a) => (a, a) -> a -> a +clamp (low, high) a = min high (max a low) + +renderHeaderDefault :: + (PandocMonad m) => Int -> Attr -> [Inline] -> RR m (Doc Text) +renderHeaderDefault level _attr inlines = + case clamp (1, 4) level of + 1 -> inlineToBBCode $ Underline [Strong inlines] + 2 -> inlineToBBCode $ Strong inlines + 3 -> inlineToBBCode $ Underline inlines + _ -> inlineListToBBCode inlines + +-- Adapted from Text.Pandoc.Writers.Org +renderLinkDefault :: + (PandocMonad m) => Attr -> [Inline] -> Target -> RR m (Doc Text) +renderLinkDefault _ txt (src, _) = + case txt of + [Str x] + | escapeURI x == src -> + pure $ "[url]" <> literal x <> "[/url]" + _ -> do + contents <- inlineListToBBCode txt + let suffix = if T.null src then "" else "=" <> src + pure $ "[url" <> literal suffix <> "]" <> contents <> "[/url]" + +renderCodeBlockDefault :: (PandocMonad m) => Attr -> Text -> RR m (Doc Text) +renderCodeBlockDefault (_, cls, _) code = do + let opening = case cls of + (lang : _) -> "[code=" <> lang <> "]" + _ -> "[code]" + pure $ mconcat [literal opening, literal code, cr, "[/code]"] + +renderCodeBlockSimple :: (PandocMonad m) => Attr -> Text -> RR m (Doc Text) +renderCodeBlockSimple _ code = do + pure $ mconcat [literal "[code]", literal code, cr, "[/code]"] + +renderInlineCodeLiteral :: (PandocMonad m) => Attr -> Text -> RR m (Doc Text) +renderInlineCodeLiteral _ code = pure $ literal code + +renderInlineCodeNoParse :: (PandocMonad m) => Attr -> Text -> RR m (Doc Text) +renderInlineCodeNoParse _ code = + pure $ mconcat [literal "[noparse]", literal code, "[/noparse]"] + +renderInlineCodeHubzilla :: (PandocMonad m) => Attr -> Text -> RR m (Doc Text) +renderInlineCodeHubzilla _ code = + pure $ mconcat [literal "[code]", literal code, "[/code]"] + +renderInlineCodeXenforo :: (PandocMonad m) => Attr -> Text -> RR m (Doc Text) +renderInlineCodeXenforo _ code = + pure $ mconcat [literal "[icode]", literal code, "[/icode]"] + +renderStrikeoutDefault :: (PandocMonad m) => [Inline] -> RR m (Doc Text) +renderStrikeoutDefault inlines = do + contents <- inlineListToBBCode inlines + pure $ mconcat ["[s]", contents, "[/s]"] + +renderStrikeoutSteam :: (PandocMonad m) => [Inline] -> RR m (Doc Text) +renderStrikeoutSteam inlines = do + contents <- inlineListToBBCode inlines + pure $ mconcat ["[strike]", contents, "[/strike]"] + +renderDefinitionListDefault :: + (PandocMonad m) => [([Inline], [[Block]])] -> RR m (Doc Text) +renderDefinitionListDefault items = do + items' <- forM items $ \(term, definitions) -> do + term' <- inlineListToBBCode term + definitions' <- blockToBBCode (BulletList definitions) + pure $ term' $$ definitions' + pure $ vcat items' + +renderDefinitionListHubzilla :: + (PandocMonad m) => [([Inline], [[Block]])] -> RR m (Doc Text) +renderDefinitionListHubzilla items = do + items' <- forM items $ \(term, definitions) -> do + term' <- inlineListToBBCode term + let term'' = "[*= " <> term' <> "]" + definitions' <- forM definitions blockListToBBCode + pure $ vcat (term'' : definitions') + pure $ vcat (literal "[dl terms=\"b\"]" : items' ++ [literal "[/dl]"]) + +listWithTags :: + (PandocMonad m) => + Text -> + Text -> + ([[Block]] -> RR m [Doc Text]) -> + [[Block]] -> + RR m (Doc Text) +listWithTags open close renderItems items = do + contents <- local (\s -> s{inList = True}) (renderItems items) + pure $ vcat $ literal open : contents ++ [literal close] + +starListItems :: (PandocMonad m) => [[Block]] -> RR m [Doc Text] +starListItems items = forM items $ \item -> do + item' <- blockListToBBCode item + pure $ literal "[*]" <> item' + +listStyleCode :: ListNumberStyle -> Maybe Text +listStyleCode = \case + Decimal -> Just "1" + DefaultStyle -> Just "1" + LowerAlpha -> Just "a" + UpperAlpha -> Just "A" + LowerRoman -> Just "i" + UpperRoman -> Just "I" + Example -> Nothing + +renderBulletListOfficial :: (PandocMonad m) => [[Block]] -> RR m (Doc Text) +renderBulletListOfficial = listWithTags "[list]" "[/list]" starListItems + +renderBulletListHubzilla :: (PandocMonad m) => [[Block]] -> RR m (Doc Text) +renderBulletListHubzilla = listWithTags "[ul]" "[/ul]" starListItems + +renderOrderedListHubzilla :: + (PandocMonad m) => ListAttributes -> [[Block]] -> RR m (Doc Text) +renderOrderedListHubzilla (_, style, _) = case style of + DefaultStyle -> listWithTags "[ol]" "[/ol]" starListItems + Example -> listWithTags "[ol]" "[/ol]" starListItems + _ -> listWithTags ("[list=" <> suffix <> "]") "[/list]" starListItems + where + suffix = fromMaybe "1" $ listStyleCode style + +renderOrderedListOfficial :: + (PandocMonad m) => ListAttributes -> [[Block]] -> RR m (Doc Text) +renderOrderedListOfficial (_, style, _) = do + let suffix = maybe "" ("=" <>) (listStyleCode style) + listWithTags ("[list" <> suffix <> "]") "[/list]" starListItems + +renderOrderedListSteam :: + (PandocMonad m) => ListAttributes -> [[Block]] -> RR m (Doc Text) +renderOrderedListSteam _ = + listWithTags "[olist]" "[/olist]" starListItems + +renderHeaderSteam :: + (PandocMonad m) => Int -> Attr -> [Inline] -> RR m (Doc Text) +renderHeaderSteam level _ inlines = do + body <- inlineListToBBCode inlines + let capped = clamp (1, 3) level + open = "[h" <> tshow capped <> "]" + close = "[/h" <> tshow capped <> "]" + pure $ literal open <> body <> literal close + +renderHeaderHubzilla :: + (PandocMonad m) => Int -> Attr -> [Inline] -> RR m (Doc Text) +renderHeaderHubzilla level _ inlines = do + body <- inlineListToBBCode inlines + let capped = clamp (1, 6) level + open = "[h" <> tshow capped <> "]" + close = "[/h" <> tshow capped <> "]" + pure $ literal open <> body <> literal close + +-- xenForo supports levels 1--3, but levels other than 1--3 become div with +-- .bbHeading class which can be linked to. +renderHeaderXenforo :: + (PandocMonad m) => Int -> Attr -> [Inline] -> RR m (Doc Text) +renderHeaderXenforo level _ inlines = do + body <- inlineListToBBCode inlines + let capped = max 1 level + open = "[heading=" <> tshow capped <> "]" + close = "[/heading]" + pure $ literal open <> body <> literal close + +renderTableGeneric :: + (PandocMonad m) => + Text -> + Text -> + Text -> + (Attr, Caption, [ColSpec], TableHead, [TableBody], TableFoot) -> + RR m (Doc Text) +renderTableGeneric tableTag headerCellTag bodyCellTag table = do + caption' <- inlineListToBBCode caption + table' <- + if not simpleCells + then "" <$ report (BlockNotRendered tableBlock) + else do + headerDocs <- + if null headers + then pure [] + else pure <$> renderTableRow headerCellTag headers + rowDocs <- mapM (renderTableRow bodyCellTag) rows + pure $ renderTable' headerDocs rowDocs + pure $ caption' $$ table' + where + (attr, blkCapt, specs, thead, tbody, tfoot) = table + (caption, _, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot + tableBlock = Table attr blkCapt specs thead tbody tfoot + simpleCells = onlySimpleTableCells (headers : rows) + renderTable' headerDocs rowDocs = + vcat + [ literal ("[" <> tableTag <> "]") + , vcat headerDocs + , vcat rowDocs + , literal ("[/" <> tableTag <> "]") + ] + renderCell cellTag cellDoc = + mconcat + [ literal ("[" <> cellTag <> "]") + , cellDoc + , literal ("[/" <> cellTag <> "]") + ] + renderTableRow cellTag cells = do + renderedCells <- mapM blockListToBBCode cells + let cellsDoc = mconcat $ map (renderCell cellTag) renderedCells + pure $ literal "[tr]" <> cellsDoc <> literal "[/tr]" + +renderTableDefault :: + (PandocMonad m) => + ( Attr + , Caption + , [ColSpec] + , TableHead + , [TableBody] + , TableFoot + ) -> + RR m (Doc Text) +renderTableDefault = renderTableGeneric "table" "th" "td" + +renderTableOmit :: + (PandocMonad m) => + ( Attr + , Caption + , [ColSpec] + , TableHead + , [TableBody] + , TableFoot + ) -> + RR m (Doc Text) +renderTableOmit (_, blkCapt, specs, thead, tbody, tfoot) = do + let (caption, _, _, _, _) = toLegacyTable blkCapt specs thead tbody tfoot + caption' <- inlineListToBBCode caption + pure $ caption' $$ "(TABLE)" + +-- $wrapping_spans_divs +-- Consider attribute a key-value pair with a Just value, and respectively +-- class is key-value pair with Nothing value. +-- For instance, given @("", ["cl1"], [("k", "v")]) :: 'Attr'@, respective Map +-- should look like @'Map.fromList' [("cl1", 'Nothing'), ("k", 'Just' "v")]@ +-- +-- This transformation is handled by 'attrToMap' +-- +-- Example definition of a wrapSpanDiv: +-- +-- > {-# LANGUAGE OverloadedStrings #-} +-- > import Data.Map (Map) +-- > import qualified Data.Map as Map +-- > import Text.DocLayout +-- > import Data.Text (Text) +-- > import qualified Data.Text as T +-- > +-- > wrapSpanDivSteam :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text +-- > wrapSpanDivSteam isDiv kvc doc = Map.foldrWithKey wrap doc kvc +-- > where +-- > wrap "spoiler" (Just _) acc | isDiv = "[spoiler]" <> acc <> "[/spoiler]" +-- > wrap "spoiler" Nothing acc | isDiv = "[spoiler]" <> acc <> "[/spoiler]" +-- > wrap _ _ acc = acc +-- +-- To verify it works, wrap some text in unnamed spoiler +-- +-- >>> render Nothing $ wrapSpanDivSteam True (attrToMap ("", ["spoiler"], [])) "I am text" +-- "[spoiler]I am text[/spoiler]" + +{- | The goal of the transformation is to treat classes and key-value pairs +uniformly. + +Class list becomes Map where all values are Nothing, and list of key-value +pairs is converted to Map via 'Map.toList'. Both Maps are then merged. +-} +attrToMap :: Attr -> Map Text (Maybe Text) +attrToMap (_, classes, kvList) = + Map.fromList kvList' `Map.union` Map.fromList classes' + where + kvList' = map (\(k, v) -> (k, Just v)) kvList + classes' = map (\k -> (k, Nothing)) classes + +wrapSpanDivOfficial :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text +wrapSpanDivOfficial isDiv kvc doc = Map.foldrWithKey wrap doc kvc + where + wrap "left" Nothing acc | isDiv = "[left]" <> acc <> "[/left]" + wrap "center" Nothing acc | isDiv = "[center]" <> acc <> "[/center]" + wrap "right" Nothing acc | isDiv = "[right]" <> acc <> "[/right]" + wrap "spoiler" Nothing acc | isDiv = "[spoiler]" <> acc <> "[/spoiler]" + wrap "spoiler" (Just v) acc + | isDiv = + literal ("[spoiler=" <> T.filter notBracket v <> "]") + <> acc + <> "[/spoiler]" + wrap "size" (Just v) acc + | Just v' <- readMaybe @Int (T.unpack v) + , v' > 0 = + literal ("[size=" <> v <> "]") <> acc <> "[/size]" + wrap "color" (Just v) acc = + literal ("[color=" <> v <> "]") <> acc <> "[/color]" + wrap _ _ acc = acc + +wrapSpanDivSteam :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text +wrapSpanDivSteam isDiv kvc doc = Map.foldrWithKey wrap doc kvc + where + wrap "spoiler" (Just _) acc | isDiv = "[spoiler]" <> acc <> "[/spoiler]" + wrap "spoiler" Nothing acc | isDiv = "[spoiler]" <> acc <> "[/spoiler]" + wrap _ _ acc = acc + +wrapSpanDivPhpBB :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text +wrapSpanDivPhpBB _ kvc doc = Map.foldrWithKey wrap doc kvc + where + wrap "color" (Just v) acc = + literal ("[color=" <> v <> "]") <> acc <> "[/color]" + wrap _ _ acc = acc + +wrapSpanDivFluxBB :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text +wrapSpanDivFluxBB _ kvc doc = Map.foldrWithKey wrap doc kvc + where + wrap "color" (Just v) acc = + literal ("[color=" <> v <> "]") <> acc <> "[/color]" + wrap _ _ acc = acc + +wrapSpanDivHubzilla :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text +wrapSpanDivHubzilla isDiv kvc doc = Map.foldrWithKey wrap doc kvc + where + wrap "center" Nothing acc | isDiv = "[center]" <> acc <> "[/center]" + wrap "spoiler" Nothing acc | isDiv = "[spoiler]" <> acc <> "[/spoiler]" + wrap "spoiler" (Just v) acc + | isDiv = + literal ("[spoiler=" <> T.filter notBracket v <> "]") + <> acc + <> "[/spoiler]" + wrap "size" (Just v) acc + | Just v' <- readMaybe @Int (T.unpack v) + , v' > 0 = + literal ("[size=" <> v <> "]") <> acc <> "[/size]" + wrap "color" (Just v) acc = + literal ("[color=" <> v <> "]") <> acc <> "[/color]" + wrap "font" (Just v) acc = literal ("[font=" <> v <> "]") <> acc <> "[/font]" + wrap _ _ acc = acc + +wrapSpanDivXenforo :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text +wrapSpanDivXenforo isDiv kvc doc = Map.foldrWithKey wrap doc kvc + where + wrap "left" Nothing acc | isDiv = "[left]" <> acc <> "[/left]" + wrap "center" Nothing acc | isDiv = "[center]" <> acc <> "[/center]" + wrap "right" Nothing acc | isDiv = "[right]" <> acc <> "[/right]" + wrap "spoiler" _ acc | not isDiv = "[ispoiler]" <> acc <> "[/ispoiler]" + wrap "spoiler" Nothing acc | isDiv = "[spoiler]" <> acc <> "[/spoiler]" + wrap "spoiler" (Just v) acc + | isDiv = + literal ("[spoiler=" <> T.filter notBracket v <> "]") + <> acc + <> "[/spoiler]" + wrap "size" (Just v) acc + | Just v' <- readMaybe @Int (T.unpack v) + , v' > 0 = + literal ("[size=" <> v <> "]") <> acc <> "[/size]" + wrap "color" (Just v) acc = + literal ("[color=" <> v <> "]") <> acc <> "[/color]" + wrap "font" (Just v) acc = literal ("[font=" <> v <> "]") <> acc <> "[/font]" + wrap _ _ acc = acc + +renderOrderedListFluxbb :: + (PandocMonad m) => + ListAttributes -> + [[Block]] -> + RR m (Doc Text) +renderOrderedListFluxbb (_, style, _) = + let suffix = case style of + LowerAlpha -> "=a" + UpperAlpha -> "=a" + _ -> "=1" + in listWithTags ("[list" <> suffix <> "]") "[/list]" starListItems + +renderOrderedListXenforo :: + (PandocMonad m) => + ListAttributes -> + [[Block]] -> + RR m (Doc Text) +renderOrderedListXenforo _ = + listWithTags "[list=1]" "[/list]" starListItems + +renderLinkEmailAware :: + (PandocMonad m) => + Attr -> + [Inline] -> + Target -> + RR m (Doc Text) +renderLinkEmailAware attr txt target@(src, _) = do + case T.stripPrefix "mailto:" src of + Just address -> do + linkText <- inlineListToBBCode txt + let isAutoEmail = case txt of + [Str x] -> x == address + _ -> False + pure $ + if isAutoEmail + then literal "[email]" <> literal address <> "[/email]" + else literal ("[email=" <> address <> "]") <> linkText <> "[/email]" + Nothing -> renderLinkDefault attr txt target + +renderBlockQuoteDefault :: (PandocMonad m) => [Block] -> RR m (Doc Text) +renderBlockQuoteDefault blocks = do + contents <- blockListToBBCode blocks + pure $ vcat ["[quote]", contents, "[/quote]"] + +renderBlockQuoteFluxBB :: (PandocMonad m) => [Block] -> RR m (Doc Text) +renderBlockQuoteFluxBB blocks = do + contents <- blockListToBBCode blocks + isInList <- asks inList + if isInList + then "" <$ report (BlockNotRendered $ BlockQuote blocks) + else pure $ vcat ["[quote]", contents, "[/quote]"] + +renderHorizontalRuleDefault :: (PandocMonad m) => RR m (Doc Text) +renderHorizontalRuleDefault = pure "* * *" + +renderHorizontalRuleHR :: (PandocMonad m) => RR m (Doc Text) +renderHorizontalRuleHR = pure "[hr]" + +renderLineBlockDefault :: (PandocMonad m) => [[Inline]] -> RR m (Doc Text) +renderLineBlockDefault inliness = vcat <$> mapM inlineListToBBCode inliness + +renderParaDefault :: (PandocMonad m) => [Inline] -> RR m (Doc Text) +renderParaDefault inlines = inlineListToBBCode inlines + +renderSuperscriptDefault :: (PandocMonad m) => [Inline] -> RR m (Doc Text) +renderSuperscriptDefault = inlineListToBBCode + +renderSubscriptDefault :: (PandocMonad m) => [Inline] -> RR m (Doc Text) +renderSubscriptDefault = inlineListToBBCode + +renderSmallCapsDefault :: (PandocMonad m) => [Inline] -> RR m (Doc Text) +renderSmallCapsDefault = inlineListToBBCode + +renderCiteDefault :: + (PandocMonad m) => [Citation] -> [Inline] -> RR m (Doc Text) +renderCiteDefault _ = inlineListToBBCode + +renderNoteDefault :: (PandocMonad m) => [Block] -> RR m (Doc Text) +renderNoteDefault blocks = do + -- NOTE: no BBCode flavor has native syntax for footnotes. + newN <- gets (succ . Seq.length) + contents <- blockListToBBCode blocks + let pointer = "(" <> tshow newN <> ")" + let contents' = literal pointer <> space <> contents + modify (|> contents') + pure $ literal pointer + +renderFigureDefault :: + (PandocMonad m) => Attr -> Caption -> [Block] -> RR m (Doc Text) +renderFigureDefault _ (Caption _ caption) blocks = do + caption' <- blockListToBBCode caption + contents <- blockListToBBCode blocks + pure $ contents $$ caption' + +renderQuotedDefault :: + (PandocMonad m) => QuoteType -> [Inline] -> RR m (Doc Text) +renderQuotedDefault typ inlines = do + let quote = case typ of SingleQuote -> "'"; DoubleQuote -> "\"" + contents <- inlineListToBBCode inlines + pure $ mconcat [quote, contents, quote] + +renderMathDefault :: (PandocMonad m) => MathType -> Text -> RR m (Doc Text) +renderMathDefault typ math = case typ of + InlineMath -> + inlineToBBCode $ + Code ("", ["latex"], []) ("$" <> math <> "$") + DisplayMath -> + blockToBBCode $ + CodeBlock ("", ["latex"], []) ("$$" <> math <> "$$") + +{- | Format documentation: + +There is no such thing as «Official» bbcode format, nonetheless this spec +implements what is described on bbcode.org, which is a reasonable base that can +be extended/contracted as needed. +-} +officialSpec :: FlavorSpec +officialSpec = + FlavorSpec + { renderOrderedList = renderOrderedListOfficial + , renderBulletList = renderBulletListOfficial + , renderDefinitionList = renderDefinitionListDefault + , renderHeader = renderHeaderDefault + , renderTable = renderTableDefault + , renderLink = renderLinkEmailAware + , renderCodeBlock = renderCodeBlockDefault + , renderInlineCode = renderInlineCodeLiteral + , renderStrikeout = renderStrikeoutDefault + , renderBlockQuote = renderBlockQuoteDefault + , renderHorizontalRule = renderHorizontalRuleDefault + , renderLineBlock = renderLineBlockDefault + , renderPara = renderParaDefault + , renderSuperscript = renderSuperscriptDefault + , renderSubscript = renderSubscriptDefault + , renderSmallCaps = renderSmallCapsDefault + , renderCite = renderCiteDefault + , renderNote = renderNoteDefault + , renderFigure = renderFigureDefault + , renderMath = renderMathDefault + , renderQuoted = renderQuotedDefault + , renderImage = renderImageDefault + , wrapSpanDiv = wrapSpanDivOfficial + } + +{- | Format documentation: + +Used at: + +Quirks: + +- There seems to be no way to show external images on steam. + https://steamcommunity.com/sharedfiles/filedetails/?id=2807121939 shows [img] + and [previewimg] can (could?) be used to show images, although it is likely + reserved for steam urls only. +-} +steamSpec :: FlavorSpec +steamSpec = + officialSpec + { renderOrderedList = renderOrderedListSteam + , renderHeader = renderHeaderSteam + , renderLink = renderLinkDefault + , renderInlineCode = renderInlineCodeNoParse + , renderStrikeout = renderStrikeoutSteam + , renderImage = renderImageOmit + , wrapSpanDiv = wrapSpanDivSteam + , renderHorizontalRule = renderHorizontalRuleHR + } + +{- | Format documentation: + +Used at: + +Quirks: + +- PhpBB docs don't mention strikeout support, but their + [support forum](https://www.phpbb.com/community) does support it. +- Same for named code blocks. +- @[email=example\@example.com]the email[/url]@ is a valid use of [email] + tag on the phpBB community forum despite not being in the docs. +-} +phpbbSpec :: FlavorSpec +phpbbSpec = + officialSpec + { renderTable = renderTableOmit + , renderImage = renderImagePhpBB + , wrapSpanDiv = wrapSpanDivPhpBB + } + +{- | Format documentation: + +Used at: https://bbs.archlinux.org +-} +fluxbbSpec :: FlavorSpec +fluxbbSpec = + officialSpec + { renderOrderedList = renderOrderedListFluxbb + , renderCodeBlock = renderCodeBlockSimple + , renderTable = renderTableOmit + , renderBlockQuote = renderBlockQuoteFluxBB + , renderImage = renderImageFluxBB + , wrapSpanDiv = wrapSpanDivFluxBB + } + +{- | Format documentation: + +Used at: (see [other hubs](https://hubzilla.org/pubsites)) + +Quirks: + +- If link target is not a URI, it simply points to https://$BASEURL/ when + rendered by a hub. +-} +hubzillaSpec :: FlavorSpec +hubzillaSpec = + officialSpec + { renderOrderedList = renderOrderedListHubzilla + , renderBulletList = renderBulletListHubzilla + , renderDefinitionList = renderDefinitionListHubzilla + , renderHeader = renderHeaderHubzilla + , renderInlineCode = renderInlineCodeHubzilla + , renderLink = renderLinkDefault + , wrapSpanDiv = wrapSpanDivHubzilla + , renderHorizontalRule = renderHorizontalRuleHR + } + +{- | Format documentation: + +Used at: see +-} +xenforoSpec :: FlavorSpec +xenforoSpec = + officialSpec + { wrapSpanDiv = wrapSpanDivXenforo + , renderHeader = renderHeaderXenforo + , renderInlineCode = renderInlineCodeXenforo + , renderHorizontalRule = renderHorizontalRuleHR + , renderOrderedList = renderOrderedListXenforo + , renderImage = renderImageXenforo + } diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index 2dcccf013006..385ee1e6695f 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -275,6 +275,7 @@ tests pandocPath = "vimdoc/headers.markdown" "vimdoc/headers-numbered.vimdoc" ] ] + , testGroup "bbcode" [testGroup "writer" $ writerTests' "bbcode"] ] where test' = test pandocPath diff --git a/test/Tests/Writers/BBCode.hs b/test/Tests/Writers/BBCode.hs new file mode 100644 index 000000000000..3f82436be8a1 --- /dev/null +++ b/test/Tests/Writers/BBCode.hs @@ -0,0 +1,355 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeApplications #-} + +module Tests.Writers.BBCode (tests) where + +import Data.Maybe (isNothing) +import Data.Text as T +import Test.Tasty +import Test.Tasty.HUnit (HasCallStack) +import Test.Tasty.QuickCheck +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder +import Text.Pandoc.Shared (tshow) +import Text.Read (readMaybe) + +bbcodeDefault + , bbcodeSteam + , bbcodePhpBB + , bbcodeFluxBB + , bbcodeHubzilla + , bbcodeXenforo :: + (ToPandoc a) => a -> Text +bbcodeDefault = purely (writeBBCode def) . toPandoc +bbcodeSteam = purely (writeBBCodeSteam def) . toPandoc +bbcodePhpBB = purely (writeBBCodePhpBB def) . toPandoc +bbcodeFluxBB = purely (writeBBCodeFluxBB def) . toPandoc +bbcodeHubzilla = purely (writeBBCodeHubzilla def) . toPandoc +bbcodeXenforo = purely (writeBBCodeXenforo def) . toPandoc + +infix 4 =:, `steam`, `phpbb`, `fluxbb`, `hubzilla`, `xenforo` +(=:) + , steam + , phpbb + , fluxbb + , hubzilla + , xenforo :: + (ToString a, ToPandoc a, HasCallStack) => + String -> + (a, Text) -> + TestTree +(=:) = test bbcodeDefault +steam = test bbcodeSteam +phpbb = test bbcodePhpBB +fluxbb = test bbcodeFluxBB +hubzilla = test bbcodeHubzilla +xenforo = test bbcodeXenforo + +spanClasses :: [Text] -> Inlines -> Inlines +spanClasses cls = spanWith ("", cls, []) + +spanAttrs :: [(Text, Text)] -> Inlines -> Inlines +spanAttrs kvList = spanWith ("", [], kvList) + +divClasses :: [Text] -> Blocks -> Blocks +divClasses cls = divWith ("", cls, []) + +divAttrs :: [(Text, Text)] -> Blocks -> Blocks +divAttrs kvList = divWith ("", [], kvList) + +tests :: [TestTree] +tests = + [ testGroup + "spans classes" + [ "left" =: spanClasses ["left"] "foo" =?> "foo" + , "center" =: spanClasses ["center"] "foo" =?> "foo" + , "right" =: spanClasses ["right"] "foo" =?> "foo" + , "spoiler" =: spanClasses ["spoiler"] "foo" =?> "foo" + ] + , testGroup + "spans attributes" + [ testProperty "incorrect size ignored" . property $ do + n <- arbitrary @String + let nInt = readMaybe @Int n + let actual = bbcodeDefault (spanAttrs [("size", T.pack n)] "foo") + pure $ isNothing nInt ==> actual === "foo" + , testProperty "size<=0 ignored" . property $ do + NonPositive n <- arbitrary @(NonPositive Int) + let actual = bbcodeDefault (spanAttrs [("size", tshow n)] "foo") + pure $ actual === "foo" + , testProperty "size>0" . property $ do + Positive n <- arbitrary @(Positive Int) + let actual = bbcodeDefault (spanAttrs [("size", tshow n)] "foo") + let expected = "[size=" <> tshow n <> "]" <> "foo[/size]" + pure $ actual === expected + , "size=20" =: spanAttrs [("size", "20")] "foo" =?> "[size=20]foo[/size]" + , "color=#AAAAAA" + =: spanAttrs [("color", "#AAAAAA")] "foo" + =?> "[color=#AAAAAA]foo[/color]" + , "spoiler ignored" + =: spanAttrs [("spoiler", "name with spaces and ]brackets[]")] "foo" + =?> "foo" + ] + , testGroup + "divs classes" + [ "left" + =: divClasses ["left"] (para "foo") + =?> "[left]foo[/left]" + , "center" + =: divClasses ["center"] (para "foo") + =?> "[center]foo[/center]" + , "right" + =: divClasses ["right"] (para "foo") + =?> "[right]foo[/right]" + , "spoiler" + =: divClasses ["spoiler"] (para "foo") + =?> "[spoiler]foo[/spoiler]" + ] + , testGroup + "divs attributes" + [ testProperty "incorrect size ignored" . property $ do + n <- arbitrary @String + let nInt = readMaybe @Int n + let actual = bbcodeDefault (divAttrs [("size", T.pack n)] $ para "foo") + pure $ isNothing nInt ==> actual === "foo" + , testProperty "size<=0 ignored" . property $ do + NonPositive n <- arbitrary @(NonPositive Int) + let actual = bbcodeDefault (divAttrs [("size", tshow n)] $ para "foo") + pure $ actual === "foo" + , testProperty "size>0" . property $ do + Positive n <- arbitrary @(Positive Int) + let actual = bbcodeDefault (divAttrs [("size", tshow n)] $ para "foo") + let expected = "[size=" <> tshow n <> "]" <> "foo[/size]" + pure $ actual === expected + , "size=20" + =: divAttrs [("size", "20")] (para "foo") + =?> "[size=20]foo[/size]" + , "color=#AAAAAA" + =: divAttrs [("color", "#AAAAAA")] (para "foo") + =?> "[color=#AAAAAA]foo[/color]" + , "spoiler" + =: divAttrs + [("spoiler", "name with spaces and ]brackets[]")] + (para "foo") + =?> "[spoiler=name with spaces and brackets]foo[/spoiler]" + ] + , testGroup + "default flavor" + [ "link" + =: link "https://example.com" "title" "label" + =?> "[url=https://example.com]label[/url]" + , "autolink" + =: link "https://example.com" "title" "https://example.com" + =?> "[url]https://example.com[/url]" + , "email autolink" + =: link + "mailto:example@example.com" + "title" + "example@example.com" + =?> "[email]example@example.com[/email]" + , "named email" + =: link "mailto:example@example.com" "title" "example email" + =?> "[email=example@example.com]example email[/email]" + , "h0" =: header 0 "heading 0" =?> "[u][b]heading 0[/b][/u]" + , "h1" =: header 1 "heading 1" =?> "[u][b]heading 1[/b][/u]" + , "h2" =: header 2 "heading 2" =?> "[b]heading 2[/b]" + , "h3" =: header 3 "heading 3" =?> "[u]heading 3[/u]" + , "h4" =: header 4 "heading 4" =?> "heading 4" + , "h5" =: header 5 "heading 5" =?> "heading 5" + ] + , testGroup + "steam" + [ test bbcodeSteam "dename spoiler" $ + divAttrs [("spoiler", "bar")] (para "foo") + =?> ("[spoiler]foo[/spoiler]" :: Text) + , testProperty "ordered list styleless" . property $ do + let listItems = [para "foo", para "bar", para "baz"] + attrsRand <- (,,) <$> arbitrary <*> arbitrary <*> arbitrary + let actual = bbcodeSteam $ orderedListWith attrsRand listItems + let expected = "[olist]\n[*]foo\n[*]bar\n[*]baz\n[/olist]" + pure $ actual === expected + , "h0" `steam` header 0 "heading 0" =?> "[h1]heading 0[/h1]" + , "h1" `steam` header 1 "heading 1" =?> "[h1]heading 1[/h1]" + , "h2" `steam` header 2 "heading 2" =?> "[h2]heading 2[/h2]" + , "h3" `steam` header 3 "heading 3" =?> "[h3]heading 3[/h3]" + , "h4" `steam` header 4 "heading 4" =?> "[h3]heading 4[/h3]" + , "code" + `steam` codeWith ("id", ["haskell"], []) "map (2^) [1..5]" + =?> "[noparse]map (2^) [1..5][/noparse]" + ] + , testGroup + "phpBB" + [ "image" + `phpbb` imageWith + ("id", [], [("width", "100")]) + "https://example.com" + "title" + "alt text" + =?> "[img]https://example.com[/img]" + ] + , testGroup + "FluxBB" + [ "image" + `fluxbb` imageWith + ("id", [], [("width", "100")]) + "https://example.com" + "title" + "alt text" + =?> "[img=alt text]https://example.com[/img]" + , testProperty "ordered list" . property $ do + let listItems = [para "foo", para "bar", para "baz"] + attrsRand <- (,,) <$> arbitrary <*> arbitrary <*> arbitrary + let actual = bbcodeFluxBB $ orderedListWith attrsRand listItems + let opening = case attrsRand of + (_, LowerAlpha, _) -> "[list=a]" + (_, UpperAlpha, _) -> "[list=a]" + _ -> "[list=1]" + let expected = opening <> "\n[*]foo\n[*]bar\n[*]baz\n[/list]" + pure $ actual === expected + , "ulist > BlockQuote not rendered" + `fluxbb` bulletList [blockQuote (para "foo") <> para "bar"] + =?> "[list]\n[*]bar\n[/list]" + , "code block" + `fluxbb` codeBlockWith + ("id", ["haskell"], []) + ( T.intercalate "\n" $ + [ "vals =" + , " take 10" + , " . filter (\\x -> (x - 5) `mod` 3 == 0)" + , " $ map (2 ^) [1 ..]" + ] + ) + =?> T.intercalate + "\n" + [ "[code]vals =" + , " take 10" + , " . filter (\\x -> (x - 5) `mod` 3 == 0)" + , " $ map (2 ^) [1 ..]" + , "[/code]" + ] + ] + , testGroup + "Hubzilla" + [ "unordered list" + `hubzilla` bulletList [para "foo", para "bar", para "baz"] + =?> "[ul]\n[*]foo\n[*]bar\n[*]baz\n[/ul]" + , testProperty "ordered list" . property $ do + let listItems = [para "foo", para "bar", para "baz"] + attrsRand <- (,,) <$> arbitrary <*> arbitrary <*> arbitrary + let actual = bbcodeHubzilla $ orderedListWith attrsRand listItems + let (opening, closing) = case attrsRand of + (_, Decimal, _) -> ("[list=1]", "[/list]") + (_, DefaultStyle, _) -> ("[ol]", "[/ol]") + (_, Example, _) -> ("[ol]", "[/ol]") + (_, LowerAlpha, _) -> ("[list=a]", "[/list]") + (_, UpperAlpha, _) -> ("[list=A]", "[/list]") + (_, LowerRoman, _) -> ("[list=i]", "[/list]") + (_, UpperRoman, _) -> ("[list=I]", "[/list]") + let expected = + opening <> "\n[*]foo\n[*]bar\n[*]baz\n" <> closing + pure $ actual === expected + , "definition list" + `hubzilla` definitionList + [ ("term_foo", [para "def_foo1", para "def_foo2"]) + , ("term_bar", [para "def_bar1", para "def_bar2"]) + , ("term_baz", [para "def_baz1", para "def_baz2"]) + ] + =?> mconcat + [ "[dl terms=\"b\"]\n" + , "[*= term_foo]\ndef_foo1\ndef_foo2\n" + , "[*= term_bar]\ndef_bar1\ndef_bar2\n" + , "[*= term_baz]\ndef_baz1\ndef_baz2\n" + , "[/dl]" + ] + , "h0" `hubzilla` header 0 "heading 0" =?> "[h1]heading 0[/h1]" + , "h1" `hubzilla` header 1 "heading 1" =?> "[h1]heading 1[/h1]" + , "h2" `hubzilla` header 2 "heading 2" =?> "[h2]heading 2[/h2]" + , "h3" `hubzilla` header 3 "heading 3" =?> "[h3]heading 3[/h3]" + , "h4" `hubzilla` header 4 "heading 4" =?> "[h4]heading 4[/h4]" + , "h5" `hubzilla` header 5 "heading 5" =?> "[h5]heading 5[/h5]" + , "h6" `hubzilla` header 6 "heading 6" =?> "[h6]heading 6[/h6]" + , "h7" `hubzilla` header 7 "heading 7" =?> "[h6]heading 7[/h6]" + , "link" + `hubzilla` link "https://example.com" "title" "label" + =?> "[url=https://example.com]label[/url]" + , "autolink" + `hubzilla` link "https://example.com" "title" "https://example.com" + =?> "[url]https://example.com[/url]" + , "email autolink" + `hubzilla` link + "mailto:example@example.com" + "title" + "example@example.com" + =?> "[url=mailto:example@example.com]example@example.com[/url]" + , "named email" + `hubzilla` link "mailto:example@example.com" "title" "example email" + =?> "[url=mailto:example@example.com]example email[/url]" + , "inline code" + `hubzilla` ( "inline code: " + <> codeWith ("id", ["haskell"], []) "map (2^) [1..5]" + ) + =?> "inline code: [code]map (2^) [1..5][/code]" + , "font" + `hubzilla` divAttrs [("font", "serif")] (para "foo") + =?> "[font=serif]foo[/font]" + ] + , testGroup + "xenForo" + [ "unordered list" + `xenforo` bulletList [para "foo", para "bar", para "baz"] + =?> "[list]\n[*]foo\n[*]bar\n[*]baz\n[/list]" + , testProperty "ordered list styleless" . property $ do + let listItems = [para "foo", para "bar", para "baz"] + attrsRand <- (,,) <$> arbitrary <*> arbitrary <*> arbitrary + let actual = bbcodeXenforo $ orderedListWith attrsRand listItems + let expected = "[list=1]\n[*]foo\n[*]bar\n[*]baz\n[/list]" + pure $ actual === expected + , "h0" `xenforo` header 0 "heading 0" =?> "[heading=1]heading 0[/heading]" + , "h1" `xenforo` header 1 "heading 1" =?> "[heading=1]heading 1[/heading]" + , "h2" `xenforo` header 2 "heading 2" =?> "[heading=2]heading 2[/heading]" + , "h3" `xenforo` header 3 "heading 3" =?> "[heading=3]heading 3[/heading]" + , "h4" `xenforo` header 4 "heading 4" =?> "[heading=4]heading 4[/heading]" + , "link" + `xenforo` link "https://example.com" "title" "label" + =?> "[url=https://example.com]label[/url]" + , "autolink" + `xenforo` link "https://example.com" "title" "https://example.com" + =?> "[url]https://example.com[/url]" + , "email autolink" + `xenforo` link + "mailto:example@example.com" + "title" + "example@example.com" + =?> "[email]example@example.com[/email]" + , "named email" + `xenforo` link "mailto:example@example.com" "title" "example email" + =?> "[email=example@example.com]example email[/email]" + , "inline code" + `xenforo` ( "inline code: " + <> codeWith ("id", ["haskell"], []) "map (2^) [1..5]" + ) + =?> "inline code: [icode]map (2^) [1..5][/icode]" + , "font" + `xenforo` divAttrs [("font", "serif")] (para "foo") + =?> "[font=serif]foo[/font]" + , "inline spoiler" + `xenforo` ("It was " <> spanClasses ["spoiler"] ("DNS") <> "!") + =?> "It was [ispoiler]DNS[/ispoiler]!" + , "image w=50% h=50%" + `xenforo` imageWith + ("", [], [("width", "50%"), ("height", "50%")]) + "https://example.com" + "title text" + "alt text" + =?> "[img alt=\"alt text\" title=\"title text\" width=50%]https://example.com[/img]" + , "image w=50 h=50" + `xenforo` imageWith + ("", [], [("width", "50"), ("height", "50")]) + "https://example.com" + "" + "" + =?> "[img]https://example.com[/img]" + ] + ] diff --git a/test/tables.bbcode b/test/tables.bbcode new file mode 100644 index 000000000000..1ab00b9e5326 --- /dev/null +++ b/test/tables.bbcode @@ -0,0 +1,60 @@ +Simple table with caption: + +Demonstration of simple table syntax. +[table] +[tr][th]Right[/th][th]Left[/th][th]Center[/th][th]Default[/th][/tr] +[tr][td]12[/td][td]12[/td][td]12[/td][td]12[/td][/tr] +[tr][td]123[/td][td]123[/td][td]123[/td][td]123[/td][/tr] +[tr][td]1[/td][td]1[/td][td]1[/td][td]1[/td][/tr] +[/table] + +Simple table without caption: + +[table] +[tr][th]Right[/th][th]Left[/th][th]Center[/th][th]Default[/th][/tr] +[tr][td]12[/td][td]12[/td][td]12[/td][td]12[/td][/tr] +[tr][td]123[/td][td]123[/td][td]123[/td][td]123[/td][/tr] +[tr][td]1[/td][td]1[/td][td]1[/td][td]1[/td][/tr] +[/table] + +Simple table indented two spaces: + +Demonstration of simple table syntax. +[table] +[tr][th]Right[/th][th]Left[/th][th]Center[/th][th]Default[/th][/tr] +[tr][td]12[/td][td]12[/td][td]12[/td][td]12[/td][/tr] +[tr][td]123[/td][td]123[/td][td]123[/td][td]123[/td][/tr] +[tr][td]1[/td][td]1[/td][td]1[/td][td]1[/td][/tr] +[/table] + +Multiline table with caption: + +Here's the caption. It may span multiple lines. +[table] +[tr][th]Centered Header[/th][th]Left Aligned[/th][th]Right Aligned[/th][th]Default aligned[/th][/tr] +[tr][td]First[/td][td]row[/td][td]12.0[/td][td]Example of a row that spans multiple lines.[/td][/tr] +[tr][td]Second[/td][td]row[/td][td]5.0[/td][td]Here's another one. Note the blank line between rows.[/td][/tr] +[/table] + +Multiline table without caption: + +[table] +[tr][th]Centered Header[/th][th]Left Aligned[/th][th]Right Aligned[/th][th]Default aligned[/th][/tr] +[tr][td]First[/td][td]row[/td][td]12.0[/td][td]Example of a row that spans multiple lines.[/td][/tr] +[tr][td]Second[/td][td]row[/td][td]5.0[/td][td]Here's another one. Note the blank line between rows.[/td][/tr] +[/table] + +Table without column headers: + +[table] +[tr][td]12[/td][td]12[/td][td]12[/td][td]12[/td][/tr] +[tr][td]123[/td][td]123[/td][td]123[/td][td]123[/td][/tr] +[tr][td]1[/td][td]1[/td][td]1[/td][td]1[/td][/tr] +[/table] + +Multiline table without column headers: + +[table] +[tr][td]First[/td][td]row[/td][td]12.0[/td][td]Example of a row that spans multiple lines.[/td][/tr] +[tr][td]Second[/td][td]row[/td][td]5.0[/td][td]Here's another one. Note the blank line between rows.[/td][/tr] +[/table] diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index 6c6c2d1d4746..80d4ada7f6d7 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -50,6 +50,7 @@ import qualified Tests.Writers.RST import qualified Tests.Writers.AnnotatedTable import qualified Tests.Writers.TEI import qualified Tests.Writers.Markua +import qualified Tests.Writers.BBCode import qualified Tests.XML import qualified Tests.MediaBag import Text.Pandoc.Shared (inDirectory) @@ -82,6 +83,7 @@ tests pandocPath = testGroup "pandoc tests" , testGroup "PowerPoint" Tests.Writers.Powerpoint.tests , testGroup "Ms" Tests.Writers.Ms.tests , testGroup "AnnotatedTable" Tests.Writers.AnnotatedTable.tests + , testGroup "BBCode" Tests.Writers.BBCode.tests ] , testGroup "Readers" [ testGroup "LaTeX" Tests.Readers.LaTeX.tests diff --git a/test/writer.bbcode b/test/writer.bbcode new file mode 100644 index 000000000000..b81451659c5f --- /dev/null +++ b/test/writer.bbcode @@ -0,0 +1,729 @@ +This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite. + +* * * + +[u][b]Headers[/b][/u] + +[b]Level 2 with an [url=/url]embedded link[/url][/b] + +[u]Level 3 with [i]emphasis[/i][/u] + +Level 4 + +Level 5 + +[u][b]Level 1[/b][/u] + +[b]Level 2 with [i]emphasis[/i][/b] + +[u]Level 3[/u] + +with no blank line + +[b]Level 2[/b] + +with no blank line + +* * * + +[u][b]Paragraphs[/b][/u] + +Here's a regular paragraph. + +In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. + +Here's one with a bullet. * criminey. + +There should be a hard line break +here. + +* * * + +[u][b]Block Quotes[/b][/u] + +E-mail style: + +[quote] +This is a block quote. It is pretty short. +[/quote] + +[quote] +Code in a block quote: + +[code]sub status { + print "working"; +} +[/code] + +A list: + +[list=1] +[*]item one +[*]item two +[/list] + +Nested block quotes: + +[quote] +nested +[/quote] + +[quote] +nested +[/quote] +[/quote] + +This should not be a block quote: 2 > 1. + +And a following paragraph. + +* * * + +[u][b]Code Blocks[/b][/u] + +Code: + +[code]---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab +[/code] + +And: + +[code] this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{ +[/code] + +* * * + +[u][b]Lists[/b][/u] + +[b]Unordered[/b] + +Asterisks tight: + +[list] +[*]asterisk 1 +[*]asterisk 2 +[*]asterisk 3 +[/list] + +Asterisks loose: + +[list] +[*]asterisk 1 +[*]asterisk 2 +[*]asterisk 3 +[/list] + +Pluses tight: + +[list] +[*]Plus 1 +[*]Plus 2 +[*]Plus 3 +[/list] + +Pluses loose: + +[list] +[*]Plus 1 +[*]Plus 2 +[*]Plus 3 +[/list] + +Minuses tight: + +[list] +[*]Minus 1 +[*]Minus 2 +[*]Minus 3 +[/list] + +Minuses loose: + +[list] +[*]Minus 1 +[*]Minus 2 +[*]Minus 3 +[/list] + +[b]Ordered[/b] + +Tight: + +[list=1] +[*]First +[*]Second +[*]Third +[/list] + +and: + +[list=1] +[*]One +[*]Two +[*]Three +[/list] + +Loose using tabs: + +[list=1] +[*]First +[*]Second +[*]Third +[/list] + +and using spaces: + +[list=1] +[*]One +[*]Two +[*]Three +[/list] + +Multiple paragraphs: + +[list=1] +[*]Item 1, graf one. + +Item 1. graf two. The quick brown fox jumped over the lazy dog's back. +[*]Item 2. +[*]Item 3. +[/list] + +[b]Nested[/b] + +[list] +[*]Tab + +[list] +[*]Tab + +[list] +[*]Tab +[/list] +[/list] +[/list] + +Here's another: + +[list=1] +[*]First +[*]Second: + +[list] +[*]Fee +[*]Fie +[*]Foe +[/list] +[*]Third +[/list] + +Same thing but with paragraphs: + +[list=1] +[*]First +[*]Second: + +[list] +[*]Fee +[*]Fie +[*]Foe +[/list] +[*]Third +[/list] + +[b]Tabs and spaces[/b] + +[list] +[*]this is a list item indented with tabs +[*]this is a list item indented with spaces + +[list] +[*]this is an example list item indented with tabs +[*]this is an example list item indented with spaces +[/list] +[/list] + +[b]Fancy list markers[/b] + +[list=1] +[*]begins with 2 +[*]and now 3 + +with a continuation + +[list=i] +[*]sublist with roman numerals, starting with 4 +[*]more items + +[list=A] +[*]a subsublist +[*]a subsublist +[/list] +[/list] +[/list] + +Nesting: + +[list=A] +[*]Upper Alpha + +[list=I] +[*]Upper Roman. + +[list=1] +[*]Decimal start with 6 + +[list=a] +[*]Lower alpha with paren +[/list] +[/list] +[/list] +[/list] + +Autonumbering: + +[list=1] +[*]Autonumber. +[*]More. + +[list=1] +[*]Nested. +[/list] +[/list] + +Should not be a list item: + +M.A. 2007 + +B. Williams + +* * * + +[u][b]Definition Lists[/b][/u] + +Tight using spaces: + +apple +[list] +[*]red fruit +[/list] +orange +[list] +[*]orange fruit +[/list] +banana +[list] +[*]yellow fruit +[/list] + +Tight using tabs: + +apple +[list] +[*]red fruit +[/list] +orange +[list] +[*]orange fruit +[/list] +banana +[list] +[*]yellow fruit +[/list] + +Loose: + +apple +[list] +[*]red fruit +[/list] +orange +[list] +[*]orange fruit +[/list] +banana +[list] +[*]yellow fruit +[/list] + +Multiple blocks with italics: + +[i]apple[/i] +[list] +[*]red fruit + +contains seeds, crisp, pleasant to taste +[/list] +[i]orange[/i] +[list] +[*]orange fruit + +[code]{ orange code block } +[/code] + +[quote] +orange block quote +[/quote] +[/list] + +Multiple definitions, tight: + +apple +[list] +[*]red fruit +[*]computer +[/list] +orange +[list] +[*]orange fruit +[*]bank +[/list] + +Multiple definitions, loose: + +apple +[list] +[*]red fruit +[*]computer +[/list] +orange +[list] +[*]orange fruit +[*]bank +[/list] + +Blank line after term, indented marker, alternate markers: + +apple +[list] +[*]red fruit +[*]computer +[/list] +orange +[list] +[*]orange fruit + +[list=1] +[*]sublist +[*]sublist +[/list] +[/list] + +[u][b]HTML Blocks[/b][/u] + +Simple block on one line: + +foo + +And nested without indentation: + +foo + +bar + +Interpreted markdown in a table: + +This is [i]emphasized[/i] + +And this is [b]strong[/b] + +Here's a simple block: + +foo + +This should be a code block, though: + +[code]
+ foo +
+[/code] + +As should this: + +[code]
foo
+[/code] + +Now, nested: + +foo + +This should just be an HTML comment: + +Multiline: + +Code block: + +[code] +[/code] + +Just plain comment, with trailing spaces on the line: + +Code: + +[code]
+[/code] + +Hr's: + +* * * + +[u][b]Inline Markup[/b][/u] + +This is [i]emphasized[/i], and so [i]is this[/i]. + +This is [b]strong[/b], and so [b]is this[/b]. + +An [i][url=/url]emphasized link[/url][/i]. + +[b][i]This is strong and em.[/i][/b] + +So is [b][i]this[/i][/b] word. + +[b][i]This is strong and em.[/i][/b] + +So is [b][i]this[/i][/b] word. + +This is code: >, $, \, \$, . + +[s]This is [i]strikeout[/i].[/s] + +Superscripts: abcd a[i]hello[/i] ahello there. + +Subscripts: H2O, H23O, Hmany of themO. + +These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d. + +* * * + +[u][b]Smart quotes, ellipses, dashes[/b][/u] + +"Hello," said the spider. "'Shelob' is my name." + +'A', 'B', and 'C' are letters. + +'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.' + +'He said, "I want to go."' Were you alive in the 70's? + +Here is some quoted 'code' and a "[url=http://example.com/?foo=1&bar=2]quoted link[/url]". + +Some dashes: one---two --- three---four --- five. + +Dashes between numbers: 5--7, 255--66, 1987--1999. + +Ellipses...and...and.... + +* * * + +[u][b]LaTeX[/b][/u] + +[list] +[*] +[*]$2+2=4$ +[*]$x \in y$ +[*]$\alpha \wedge \omega$ +[*]$223$ +[*]$p$-Tree +[*]Here's some display math: [code=latex]$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ +[/code] +[*]Here's one that has a line break in it: $\alpha + \omega \times x^2$. +[/list] + +These shouldn't be math: + +[list] +[*]To get the famous equation, write $e = mc^2$. +[*]$22,000 is a [i]lot[/i] of money. So is $34,000. (It worked if "lot" is emphasized.) +[*]Shoes ($20) and socks ($5). +[*]Escaped $: $73 [i]this should be emphasized[/i] 23$. +[/list] + +Here's a LaTeX table: + +* * * + +[u][b]Special Characters[/b][/u] + +Here is some unicode: + +[list] +[*]I hat: Î +[*]o umlaut: ö +[*]section: § +[*]set membership: ∈ +[*]copyright: © +[/list] + +AT&T has an ampersand in their name. + +AT&T is another way to write it. + +This & that. + +4 < 5. + +6 > 5. + +Backslash: \ + +Backtick: ` + +Asterisk: * + +Underscore: _ + +Left brace: { + +Right brace: } + +Left bracket: [ + +Right bracket: ] + +Left paren: ( + +Right paren: ) + +Greater-than: > + +Hash: # + +Period: . + +Bang: ! + +Plus: + + +Minus: - + +* * * + +[u][b]Links[/b][/u] + +[b]Explicit[/b] + +Just a [url=/url/]URL[/url]. + +[url=/url/]URL and title[/url]. + +[url=/url/]URL and title[/url]. + +[url=/url/]URL and title[/url]. + +[url=/url/]URL and title[/url] + +[url=/url/]URL and title[/url] + +[url=/url/with_underscore]with_underscore[/url] + +[email=nobody@nowhere.net]Email link[/email] + +[url]Empty[/url]. + +[b]Reference[/b] + +Foo [url=/url/]bar[/url]. + +With [url=/url/]embedded [brackets][/url]. + +[url=/url/]b[/url] by itself should be a link. + +Indented [url=/url]once[/url]. + +Indented [url=/url]twice[/url]. + +Indented [url=/url]thrice[/url]. + +This should [not][] be a link. + +[code][not]: /url +[/code] + +Foo [url=/url/]bar[/url]. + +Foo [url=/url/]biz[/url]. + +[b]With ampersands[/b] + +Here's a [url=http://example.com/?foo=1&bar=2]link with an ampersand in the URL[/url]. + +Here's a link with an amersand in the link text: [url=http://att.com/]AT&T[/url]. + +Here's an [url=/script?foo=1&bar=2]inline link[/url]. + +Here's an [url=/script?foo=1&bar=2]inline link in pointy braces[/url]. + +[b]Autolinks[/b] + +With an ampersand: [url]http://example.com/?foo=1&bar=2[/url] + +[list] +[*]In a list? +[*][url]http://example.com/[/url] +[*]It should. +[/list] + +An e-mail address: [email]nobody@nowhere.net[/email] + +[quote] +Blockquoted: [url]http://example.com/[/url] +[/quote] + +Auto-links should not occur here: + +[code]or here: +[/code] + +* * * + +[u][b]Images[/b][/u] + +From "Voyage dans la Lune" by Georges Melies (1902): + +[img alt="lalune" title="Voyage dans la Lune"]lalune.jpg[/img] +lalune + +Here is a movie [img alt="movie"]movie.jpg[/img] icon. + +* * * + +[u][b]Footnotes[/b][/u] + +Here is a footnote reference,(1) and another.(2) This should [i]not[/i] be a footnote reference, because it contains a space.[^my note] Here is an inline note.(3) + +[quote] +Notes can go in quotes.(4) +[/quote] + +[list=1] +[*]And in list items.(5) +[/list] + +This paragraph should not be part of the note, as it is not indented. + +* * * + +(1) Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. + +(2) Here's the long note. This one contains multiple blocks. + +Subsequent blocks are indented to show that they belong to the footnote (as with list items). + +[code] { } +[/code] + +If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. + +(3) This is [i]easier[/i] to type. Inline notes may contain [url=http://google.com]links[/url] and ] verbatim characters, as well as [bracketed text]. + +(4) In quote. + +(5) In list.