| Copyright | © 2025 Aleksey Myshko <git@crii.xyz> |
|---|---|
| License | GNU GPL, version 2 or above |
| Maintainer | Aleksey Myshko <git@crii.xyz> |
| Stability | alpha |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Text.Pandoc.Writers.BBCode
Description
Conversion of Pandoc documents to various BBCode flavors.
Synopsis
- writeBBCode :: PandocMonad m => WriterOptions -> Pandoc -> m Text
- writeBBCodeOfficial :: PandocMonad m => WriterOptions -> Pandoc -> m Text
- writeBBCodeSteam :: PandocMonad m => WriterOptions -> Pandoc -> m Text
- writeBBCodePhpBB :: PandocMonad m => WriterOptions -> Pandoc -> m Text
- writeBBCodeFluxBB :: PandocMonad m => WriterOptions -> Pandoc -> m Text
- writeBBCodeHubzilla :: PandocMonad m => WriterOptions -> Pandoc -> m Text
- writeBBCodeXenforo :: PandocMonad m => WriterOptions -> Pandoc -> m Text
- data FlavorSpec = FlavorSpec {
- renderBlockQuote :: forall (m :: Type -> Type). PandocMonad m => [Block] -> RR m (Doc Text)
- renderBulletList :: forall (m :: Type -> Type). PandocMonad m => [[Block]] -> RR m (Doc Text)
- renderCodeBlock :: forall (m :: Type -> Type). PandocMonad m => Attr -> Text -> RR m (Doc Text)
- renderDefinitionList :: forall (m :: Type -> Type). PandocMonad m => [([Inline], [[Block]])] -> RR m (Doc Text)
- renderHeader :: forall (m :: Type -> Type). PandocMonad m => Int -> Attr -> [Inline] -> RR m (Doc Text)
- renderInlineCode :: forall (m :: Type -> Type). PandocMonad m => Attr -> Text -> RR m (Doc Text)
- renderLink :: forall (m :: Type -> Type). PandocMonad m => Attr -> [Inline] -> Target -> RR m (Doc Text)
- renderOrderedList :: forall (m :: Type -> Type). PandocMonad m => ListAttributes -> [[Block]] -> RR m (Doc Text)
- renderStrikeout :: forall (m :: Type -> Type). PandocMonad m => [Inline] -> RR m (Doc Text)
- renderTable :: forall (m :: Type -> Type). PandocMonad m => PandocTable -> RR m (Doc Text)
- renderHorizontalRule :: forall (m :: Type -> Type). PandocMonad m => RR m (Doc Text)
- renderLineBlock :: forall (m :: Type -> Type). PandocMonad m => [[Inline]] -> RR m (Doc Text)
- renderPara :: forall (m :: Type -> Type). PandocMonad m => [Inline] -> RR m (Doc Text)
- renderSuperscript :: forall (m :: Type -> Type). PandocMonad m => [Inline] -> RR m (Doc Text)
- renderSubscript :: forall (m :: Type -> Type). PandocMonad m => [Inline] -> RR m (Doc Text)
- renderSmallCaps :: forall (m :: Type -> Type). PandocMonad m => [Inline] -> RR m (Doc Text)
- renderCite :: forall (m :: Type -> Type). PandocMonad m => [Citation] -> [Inline] -> RR m (Doc Text)
- renderNote :: forall (m :: Type -> Type). PandocMonad m => [Block] -> RR m (Doc Text)
- renderFigure :: forall (m :: Type -> Type). PandocMonad m => Attr -> Caption -> [Block] -> RR m (Doc Text)
- renderQuoted :: forall (m :: Type -> Type). PandocMonad m => QuoteType -> [Inline] -> RR m (Doc Text)
- renderMath :: forall (m :: Type -> Type). PandocMonad m => MathType -> Text -> RR m (Doc Text)
- renderImage :: forall (m :: Type -> Type). PandocMonad m => Attr -> [Inline] -> Target -> RR m (Doc Text)
- wrapSpanDiv :: Bool -> Map Text (Maybe Text) -> Doc Text -> Doc Text
- data WriterState = WriterState {}
- type RR (m :: Type -> Type) a = StateT (Seq (Doc Text)) (ReaderT WriterState m) a
- writeBBCodeCustom :: PandocMonad m => FlavorSpec -> WriterOptions -> Pandoc -> m Text
- inlineToBBCode :: forall (m :: Type -> Type). PandocMonad m => Inline -> RR m (Doc Text)
- inlineListToBBCode :: forall (m :: Type -> Type). PandocMonad m => [Inline] -> RR m (Doc Text)
- blockToBBCode :: forall (m :: Type -> Type). PandocMonad m => Block -> RR m (Doc Text)
- blockListToBBCode :: forall (m :: Type -> Type). PandocMonad m => [Block] -> RR m (Doc Text)
- attrToMap :: Attr -> Map Text (Maybe Text)
- officialSpec :: FlavorSpec
- steamSpec :: FlavorSpec
- phpbbSpec :: FlavorSpec
- fluxbbSpec :: FlavorSpec
- hubzillaSpec :: FlavorSpec
- xenforoSpec :: FlavorSpec
Predefined writers
writeBBCode :: PandocMonad m => WriterOptions -> Pandoc -> m Text Source #
writeBBCodeOfficial :: PandocMonad m => WriterOptions -> Pandoc -> m Text Source #
writeBBCodeSteam :: PandocMonad m => WriterOptions -> Pandoc -> m Text Source #
writeBBCodePhpBB :: PandocMonad m => WriterOptions -> Pandoc -> m Text Source #
writeBBCodeFluxBB :: PandocMonad m => WriterOptions -> Pandoc -> m Text Source #
writeBBCodeHubzilla :: PandocMonad m => WriterOptions -> Pandoc -> m Text Source #
writeBBCodeXenforo :: PandocMonad m => WriterOptions -> Pandoc -> m Text Source #
Extending the writer
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 s underlying FlavorSpecwriteBBCode_* 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 FlavorSpec Source #
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}
Constructors
data WriterState Source #
Constructors
| WriterState | |
Fields
| |
Instances
| Default WriterState Source # | |
Defined in Text.Pandoc.Writers.BBCode Methods def :: WriterState # | |
type RR (m :: Type -> Type) a = StateT (Seq (Doc Text)) (ReaderT WriterState m) a Source #
The base of a renderer monad.
writeBBCodeCustom :: PandocMonad m => FlavorSpec -> WriterOptions -> Pandoc -> m Text Source #
Convert a Pandoc document to BBCode using the given FlavorSpec and
WriterOptions.
inlineToBBCode :: forall (m :: Type -> Type). PandocMonad m => Inline -> RR m (Doc Text) Source #
inlineListToBBCode :: forall (m :: Type -> Type). PandocMonad m => [Inline] -> RR m (Doc Text) Source #
blockToBBCode :: forall (m :: Type -> Type). PandocMonad m => Block -> RR m (Doc Text) Source #
blockListToBBCode :: forall (m :: Type -> Type). PandocMonad m => [Block] -> RR m (Doc Text) Source #
Handling attributes
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")]) :: , respective Map
should look like AttrfromList [("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 = accTo verify it works, wrap some text in unnamed spoiler
>>>render Nothing $ wrapSpanDivSteam True (attrToMap ("", ["spoiler"], [])) "I am text""[spoiler]I am text[/spoiler]"
attrToMap :: Attr -> Map Text (Maybe Text) Source #
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 toList. Both Maps are then merged.
Predefined flavor specifications
officialSpec :: FlavorSpec Source #
Format documentation: https://www.bbcode.org/reference.php
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.
steamSpec :: FlavorSpec Source #
Format documentation: https://steamcommunity.com/comment/ForumTopic/formattinghelp
Used at: https://steamcommunity.com/discussions/forum
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.
phpbbSpec :: FlavorSpec Source #
Format documentation: https://www.phpbb.com/community/help/bbcode
Used at: https://www.phpbb.com/community
Quirks:
- PhpBB docs don't mention strikeout support, but their support forum 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.
fluxbbSpec :: FlavorSpec Source #
Format documentation: https://web.archive.org/web/20210623155046/https://fluxbb.org/forums/help.php#bbcode
Used at: https://bbs.archlinux.org
hubzillaSpec :: FlavorSpec Source #
Format documentation: https://hubzilla.org/help/member/bbcode
Used at: https://hub.netzgemeinde.eu (see other hubs)
Quirks:
- If link target is not a URI, it simply points to https://$BASEURL/ when rendered by a hub.
xenforoSpec :: FlavorSpec Source #
Format documentation: https://www.xenfocus.com/community/help/bb-codes/
Used at: see https://xenforo.com/