{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Writers.MediaWiki ( writeMediaWiki, highlightingLangs ) where
import Control.Monad.Reader
import Control.Monad.State.Strict
import Data.Maybe (fromMaybe)
import qualified Data.List as DL
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import Data.List.NonEmpty (NonEmpty((:|)))
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Walk
import Text.DocLayout (render, literal)
import Text.Pandoc.Shared
import Text.Pandoc.URI
import Text.Pandoc.Templates (renderTemplate)
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
import Text.Pandoc.Writers.Shared
import Text.Pandoc.XML (escapeStringForXML)
data WriterState = WriterState {
WriterState -> Bool
stNotes :: Bool
, WriterState -> WriterOptions
stOptions :: WriterOptions
}
data WriterReader = WriterReader {
WriterReader -> WriterOptions
options :: WriterOptions
, WriterReader -> [Char]
listLevel :: [Char]
, WriterReader -> Bool
useTags :: Bool
}
type MediaWikiWriter m = ReaderT WriterReader (StateT WriterState m)
writeMediaWiki :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> m Text
writeMediaWiki WriterOptions
opts Pandoc
document =
let initialState :: WriterState
initialState = WriterState { stNotes :: Bool
stNotes = Bool
False, stOptions :: WriterOptions
stOptions = WriterOptions
opts }
env :: WriterReader
env = WriterReader { options :: WriterOptions
options = WriterOptions
opts, listLevel :: [Char]
listLevel = [], useTags :: Bool
useTags = Bool
False }
in forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (forall (m :: * -> *).
PandocMonad m =>
Pandoc -> MediaWikiWriter m Text
pandocToMediaWiki Pandoc
document) WriterReader
env) WriterState
initialState
pandocToMediaWiki :: PandocMonad m => Pandoc -> MediaWikiWriter m Text
pandocToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
Pandoc -> MediaWikiWriter m Text
pandocToMediaWiki (Pandoc Meta
meta [Block]
blocks) = do
WriterOptions
opts <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> WriterOptions
options
Context Text
metadata <- forall (m :: * -> *) a.
(Monad m, TemplateTarget a) =>
WriterOptions
-> ([Block] -> m (Doc a))
-> ([Inline] -> m (Doc a))
-> Meta
-> m (Context a)
metaToContext WriterOptions
opts
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. HasChars a => a -> Doc a
literal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trimr) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki)
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. HasChars a => a -> Doc a
literal forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trimr) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki)
Meta
meta
Text
body <- forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [Block]
blocks
Bool
notesExist <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stNotes
let notes :: Text
notes = if Bool
notesExist
then Text
"\n<references />"
else Text
""
let main :: Text
main = Text
body forall a. Semigroup a => a -> a -> a
<> Text
notes
let context :: Context Text
context = forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"body" Text
main
forall a b. (a -> b) -> a -> b
$ forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"toc" (WriterOptions -> Bool
writerTableOfContents WriterOptions
opts) Context Text
metadata
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case WriterOptions -> Maybe (Template Text)
writerTemplate WriterOptions
opts of
Maybe (Template Text)
Nothing -> Text
main
Just Template Text
tpl -> forall a. HasChars a => Maybe Int -> Doc a -> a
render forall a. Maybe a
Nothing forall a b. (a -> b) -> a -> b
$ forall a b.
(TemplateTarget a, ToContext a b) =>
Template a -> b -> Doc a
renderTemplate Template Text
tpl Context Text
context
escapeText :: Text -> Text
escapeText :: Text -> Text
escapeText = Text -> Text
escapeStringForXML
blockToMediaWiki :: PandocMonad m
=> Block
-> MediaWikiWriter m Text
blockToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
Block -> MediaWikiWriter m Text
blockToMediaWiki (Div Attr
attrs [Block]
bs) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [Block]
bs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. HasChars a => Maybe Int -> Doc a -> a
render forall a. Maybe a
Nothing (forall a. HasChars a => a -> Attr -> Doc a
tagWithAttrs Text
"div" Attr
attrs) forall a. Semigroup a => a -> a -> a
<> Text
"\n\n" forall a. Semigroup a => a -> a -> a
<>
Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"\n\n" forall a. Semigroup a => a -> a -> a
<> Text
"</div>"
blockToMediaWiki (Plain [Inline]
inlines) =
forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
inlines
blockToMediaWiki (SimpleFigure Attr
attr [Inline]
txt (Text
src, Text
tit)) = do
Text
capt <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
txt
Text
img <- forall (m :: * -> *).
PandocMonad m =>
Attr -> MediaWikiWriter m Text
imageToMediaWiki Attr
attr
let opt :: Text
opt = if Text -> Bool
T.null Text
tit
then
if Text -> Bool
T.null Text
capt
then Text
""
else Text
"alt=" forall a. Semigroup a => a -> a -> a
<> Text
capt
else Text
"alt=" forall a. Semigroup a => a -> a -> a
<> Text
tit
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"[[" forall a. Semigroup a => a -> a -> a
<>
Text -> [Text] -> Text
T.intercalate Text
"|"
(forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) [Text
"File:" forall a. Semigroup a => a -> a -> a
<> Text
src
, Text
"thumb"
, Text
"none"
, Text
img
, Text
opt
, Text
capt
]) forall a. Semigroup a => a -> a -> a
<>
Text
"]]\n"
blockToMediaWiki (Para [Inline]
inlines) = do
Bool
tags <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> Bool
useTags
[Char]
lev <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> [Char]
listLevel
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
inlines
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ if Bool
tags
then Text
"<p>" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"</p>"
else Text
contents forall a. Semigroup a => a -> a -> a
<> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
lev then Text
"\n" else Text
""
blockToMediaWiki (LineBlock [[Inline]]
lns) =
forall (m :: * -> *).
PandocMonad m =>
Block -> MediaWikiWriter m Text
blockToMediaWiki forall a b. (a -> b) -> a -> b
$ [[Inline]] -> Block
linesToPara [[Inline]]
lns
blockToMediaWiki b :: Block
b@(RawBlock Format
f Text
str)
| Format
f forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"mediawiki" = forall (m :: * -> *) a. Monad m => a -> m a
return Text
str
| Format
f forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"html" = forall (m :: * -> *) a. Monad m => a -> m a
return Text
str
| Bool
otherwise = Text
"" forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (Block -> LogMessage
BlockNotRendered Block
b)
blockToMediaWiki Block
HorizontalRule = forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\n-----\n"
blockToMediaWiki (Header Int
level (Text
ident,[Text]
_,[(Text, Text)]
_) [Inline]
inlines) = do
let autoId :: Text
autoId = Text -> Text -> Text -> Text
T.replace Text
" " Text
"_" forall a b. (a -> b) -> a -> b
$ forall a. Walkable Inline a => a -> Text
stringify [Inline]
inlines
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
inlines
let eqs :: Text
eqs = Int -> Text -> Text
T.replicate Int
level Text
"="
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
(if Text -> Bool
T.null Text
ident Bool -> Bool -> Bool
|| Text
autoId forall a. Eq a => a -> a -> Bool
== Text
ident
then Text
""
else Text
"<span id=\"" forall a. Semigroup a => a -> a -> a
<> Text
ident forall a. Semigroup a => a -> a -> a
<> Text
"\"></span>\n")
forall a. Semigroup a => a -> a -> a
<> Text
eqs forall a. Semigroup a => a -> a -> a
<> Text
" " forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
" " forall a. Semigroup a => a -> a -> a
<> Text
eqs forall a. Semigroup a => a -> a -> a
<> Text
"\n"
blockToMediaWiki (CodeBlock (Text
_,[Text]
classes,[(Text, Text)]
keyvals) Text
str) = do
let at :: Set Text
at = forall a. Ord a => [a] -> Set a
Set.fromList [Text]
classes forall a. Ord a => Set a -> Set a -> Set a
`Set.intersection` Set Text
highlightingLangs
let numberLines :: Bool
numberLines = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"number",Text
"numberLines", Text
"number-lines"])
[Text]
classes
let start :: Maybe Text
start = forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"startFrom" [(Text, Text)]
keyvals
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case forall a. Set a -> [a]
Set.toList Set Text
at of
[] -> Text
"<pre" forall a. Semigroup a => a -> a -> a
<> (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
classes
then Text
">"
else Text
" class=\"" forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.unwords [Text]
classes forall a. Semigroup a => a -> a -> a
<> Text
"\">") forall a. Semigroup a => a -> a -> a
<>
Text -> Text
escapeText Text
str forall a. Semigroup a => a -> a -> a
<> Text
"</pre>"
(Text
l:[Text]
_) -> Text
"<syntaxhighlight lang=\"" forall a. Semigroup a => a -> a -> a
<> Text
l forall a. Semigroup a => a -> a -> a
<> Text
"\"" forall a. Semigroup a => a -> a -> a
<>
(if Bool
numberLines then Text
" line" else Text
"") forall a. Semigroup a => a -> a -> a
<>
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" (\Text
x -> Text
" start=\"" forall a. Semigroup a => a -> a -> a
<> Text
x forall a. Semigroup a => a -> a -> a
<> Text
"\"") Maybe Text
start forall a. Semigroup a => a -> a -> a
<>
Text
">" forall a. Semigroup a => a -> a -> a
<> Text
str forall a. Semigroup a => a -> a -> a
<>
Text
"</syntaxhighlight>"
blockToMediaWiki (BlockQuote [Block]
blocks) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [Block]
blocks
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<blockquote>" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"</blockquote>"
blockToMediaWiki (Table Attr
attr Caption
capt [ColSpec]
colSpecs TableHead
thead [TableBody]
tbody TableFoot
tfoot) = do
forall (m :: * -> *).
PandocMonad m =>
Table -> MediaWikiWriter m Text
tableToMediaWiki (Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Ann.toTable Attr
attr Caption
capt [ColSpec]
colSpecs TableHead
thead [TableBody]
tbody TableFoot
tfoot)
blockToMediaWiki x :: Block
x@(BulletList [[Block]]
items) = do
Bool
tags <-
(Bool -> Bool -> Bool
|| Bool -> Bool
not (Block -> Bool
isSimpleList Block
x)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> Bool
useTags
if Bool
tags
then do
[Text]
contents <- forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\ WriterReader
s -> WriterReader
s { useTags :: Bool
useTags = Bool
True }) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
listItemToMediaWiki [[Block]]
items
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<ul>\n" forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
vcat [Text]
contents forall a. Semigroup a => a -> a -> a
<> Text
"</ul>\n"
else do
[Char]
lev <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> [Char]
listLevel
[Text]
contents <- forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterReader
s -> WriterReader
s { listLevel :: [Char]
listLevel = WriterReader -> [Char]
listLevel WriterReader
s forall a. Semigroup a => a -> a -> a
<> [Char]
"*" }) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
listItemToMediaWiki [[Block]]
items
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Text] -> Text
vcat [Text]
contents forall a. Semigroup a => a -> a -> a
<> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
lev then Text
"\n" else Text
""
blockToMediaWiki x :: Block
x@(OrderedList ListAttributes
attribs [[Block]]
items) = do
Bool
tags <-
(Bool -> Bool -> Bool
|| Bool -> Bool
not (Block -> Bool
isSimpleList Block
x)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> Bool
useTags
if Bool
tags
then do
[Text]
contents <- forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterReader
s -> WriterReader
s { useTags :: Bool
useTags = Bool
True }) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
listItemToMediaWiki [[Block]]
items
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<ol" forall a. Semigroup a => a -> a -> a
<> ListAttributes -> Text
listAttribsToText ListAttributes
attribs forall a. Semigroup a => a -> a -> a
<> Text
">\n" forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
vcat [Text]
contents forall a. Semigroup a => a -> a -> a
<> Text
"</ol>\n"
else do
[Char]
lev <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> [Char]
listLevel
[Text]
contents <- forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterReader
s -> WriterReader
s { listLevel :: [Char]
listLevel = WriterReader -> [Char]
listLevel WriterReader
s forall a. Semigroup a => a -> a -> a
<> [Char]
"#" }) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
listItemToMediaWiki [[Block]]
items
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Text] -> Text
vcat [Text]
contents forall a. Semigroup a => a -> a -> a
<> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
lev then Text
"\n" else Text
""
blockToMediaWiki x :: Block
x@(DefinitionList [([Inline], [[Block]])]
items) = do
Bool
tags <-
(Bool -> Bool -> Bool
|| Bool -> Bool
not (Block -> Bool
isSimpleList Block
x)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> Bool
useTags
if Bool
tags
then do
[Text]
contents <- forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterReader
s -> WriterReader
s { useTags :: Bool
useTags = Bool
True }) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
([Inline], [[Block]]) -> MediaWikiWriter m Text
definitionListItemToMediaWiki [([Inline], [[Block]])]
items
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<dl>\n" forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
vcat [Text]
contents forall a. Semigroup a => a -> a -> a
<> Text
"</dl>\n"
else do
[Char]
lev <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> [Char]
listLevel
[Text]
contents <- forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\WriterReader
s -> WriterReader
s { listLevel :: [Char]
listLevel = WriterReader -> [Char]
listLevel WriterReader
s forall a. Semigroup a => a -> a -> a
<> [Char]
";" }) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
([Inline], [[Block]]) -> MediaWikiWriter m Text
definitionListItemToMediaWiki [([Inline], [[Block]])]
items
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Text] -> Text
vcat [Text]
contents forall a. Semigroup a => a -> a -> a
<> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
lev then Text
"\n" else Text
""
blockToMediaWiki (Figure (Text
ident, [Text]
classes, [(Text, Text)]
kvs) Caption
_ [Block]
body) =
forall (m :: * -> *).
PandocMonad m =>
Block -> MediaWikiWriter m Text
blockToMediaWiki (Attr -> [Block] -> Block
Div (Text
ident, [Text
"figure"] forall a. Eq a => [a] -> [a] -> [a]
`DL.union` [Text]
classes, [(Text, Text)]
kvs) [Block]
body)
listAttribsToText :: ListAttributes -> Text
listAttribsToText :: ListAttributes -> Text
listAttribsToText (Int
startnum, ListNumberStyle
numstyle, ListNumberDelim
_) =
let numstyle' :: Text
numstyle' = Text -> Text
camelCaseToHyphenated forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> Text
tshow ListNumberStyle
numstyle
in (if Int
startnum forall a. Eq a => a -> a -> Bool
/= Int
1
then Text
" start=\"" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
tshow Int
startnum forall a. Semigroup a => a -> a -> a
<> Text
"\""
else Text
"") forall a. Semigroup a => a -> a -> a
<>
(if ListNumberStyle
numstyle forall a. Eq a => a -> a -> Bool
/= ListNumberStyle
DefaultStyle
then Text
" style=\"list-style-type: " forall a. Semigroup a => a -> a -> a
<> Text
numstyle' forall a. Semigroup a => a -> a -> a
<> Text
";\""
else Text
"")
listItemToMediaWiki :: PandocMonad m => [Block] -> MediaWikiWriter m Text
listItemToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
listItemToMediaWiki [Block]
items = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [Block]
items
Bool
tags <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> Bool
useTags
if Bool
tags
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<li>" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"</li>"
else do
[Char]
marker <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> [Char]
listLevel
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack [Char]
marker forall a. Semigroup a => a -> a -> a
<> Text
" " forall a. Semigroup a => a -> a -> a
<> Text
contents
definitionListItemToMediaWiki :: PandocMonad m
=> ([Inline],[[Block]])
-> MediaWikiWriter m Text
definitionListItemToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
([Inline], [[Block]]) -> MediaWikiWriter m Text
definitionListItemToMediaWiki ([Inline]
label, [[Block]]
items) = do
Text
labelText <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
label
[Text]
contents <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [[Block]]
items
Bool
tags <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> Bool
useTags
if Bool
tags
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<dt>" forall a. Semigroup a => a -> a -> a
<> Text
labelText forall a. Semigroup a => a -> a -> a
<> Text
"</dt>\n" forall a. Semigroup a => a -> a -> a
<>
Text -> [Text] -> Text
T.intercalate Text
"\n" (forall a b. (a -> b) -> [a] -> [b]
map (\Text
d -> Text
"<dd>" forall a. Semigroup a => a -> a -> a
<> Text
d forall a. Semigroup a => a -> a -> a
<> Text
"</dd>") [Text]
contents)
else do
[Char]
marker <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> [Char]
listLevel
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack [Char]
marker forall a. Semigroup a => a -> a -> a
<> Text
" " forall a. Semigroup a => a -> a -> a
<> Text
labelText forall a. Semigroup a => a -> a -> a
<> Text
"\n" forall a. Semigroup a => a -> a -> a
<>
Text -> [Text] -> Text
T.intercalate Text
"\n" (forall a b. (a -> b) -> [a] -> [b]
map (\Text
d -> [Char] -> Text
T.pack (forall a. [a] -> [a]
init [Char]
marker) forall a. Semigroup a => a -> a -> a
<> Text
": " forall a. Semigroup a => a -> a -> a
<> Text
d) [Text]
contents)
isSimpleList :: Block -> Bool
isSimpleList :: Block -> Bool
isSimpleList Block
x =
case Block
x of
BulletList [[Block]]
items -> forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Block] -> Bool
isSimpleListItem [[Block]]
items
OrderedList (Int
num, ListNumberStyle
sty, ListNumberDelim
_) [[Block]]
items -> forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Block] -> Bool
isSimpleListItem [[Block]]
items Bool -> Bool -> Bool
&&
Int
num forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
&& ListNumberStyle
sty forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ListNumberStyle
DefaultStyle, ListNumberStyle
Decimal]
DefinitionList [([Inline], [[Block]])]
items -> forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Block] -> Bool
isSimpleListItem forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a b. (a, b) -> b
snd [([Inline], [[Block]])]
items
Block
_ -> Bool
False
isSimpleListItem :: [Block] -> Bool
isSimpleListItem :: [Block] -> Bool
isSimpleListItem [] = Bool
True
isSimpleListItem [Block
x] =
case Block
x of
Plain [Inline]
_ -> Bool
True
Para [Inline]
_ -> Bool
True
BulletList [[Block]]
_ -> Block -> Bool
isSimpleList Block
x
OrderedList ListAttributes
_ [[Block]]
_ -> Block -> Bool
isSimpleList Block
x
DefinitionList [([Inline], [[Block]])]
_ -> Block -> Bool
isSimpleList Block
x
Block
_ -> Bool
False
isSimpleListItem [Block
x, Block
y] | Block -> Bool
isPlainOrPara Block
x =
case Block
y of
BulletList [[Block]]
_ -> Block -> Bool
isSimpleList Block
y
OrderedList ListAttributes
_ [[Block]]
_ -> Block -> Bool
isSimpleList Block
y
DefinitionList [([Inline], [[Block]])]
_ -> Block -> Bool
isSimpleList Block
y
Block
_ -> Bool
False
isSimpleListItem [Block]
_ = Bool
False
isPlainOrPara :: Block -> Bool
isPlainOrPara :: Block -> Bool
isPlainOrPara (Plain [Inline]
_) = Bool
True
isPlainOrPara (Para [Inline]
_) = Bool
True
isPlainOrPara Block
_ = Bool
False
vcat :: [Text] -> Text
vcat :: [Text] -> Text
vcat = Text -> [Text] -> Text
T.intercalate Text
"\n"
tableToMediaWiki :: PandocMonad m => Ann.Table -> MediaWikiWriter m Text
tableToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
Table -> MediaWikiWriter m Text
tableToMediaWiki (Ann.Table Attr
attr Caption
capt [ColSpec]
_ TableHead
thead [TableBody]
tbodies TableFoot
tfoot) = do
let (Text
ident,[Text]
classes,[(Text, Text)]
kvs) = Attr
attr
[Text]
caption <- case Caption
capt of
Caption Maybe [Inline]
_ [] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty
Caption Maybe [Inline]
_ [Block]
longCapt -> do
Text
c <- forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [Block]
longCapt
forall (m :: * -> *) a. Monad m => a -> m a
return [ Text
"|+ " forall a. Semigroup a => a -> a -> a
<> Text -> Text
trimr Text
c ]
[Text]
head' <- forall (m :: * -> *).
PandocMonad m =>
TableHead -> MediaWikiWriter m [Text]
tableHeadToMW TableHead
thead
[Text]
bodies' <- forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
TableBody -> MediaWikiWriter m [Text]
tableBodyToMW [TableBody]
tbodies
[Text]
foot' <- forall (m :: * -> *).
PandocMonad m =>
TableFoot -> MediaWikiWriter m [Text]
tableFootToMW TableFoot
tfoot
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines forall a b. (a -> b) -> a -> b
$ [
Text
"{|" forall a. Semigroup a => a -> a -> a
<> (forall a. HasChars a => Maybe Int -> Doc a -> a
render forall a. Maybe a
Nothing (forall a. HasChars a => Attr -> Doc a
htmlAttrs (Text
ident, Text
"wikitable"forall a. a -> [a] -> [a]
:[Text]
classes, [(Text, Text)]
kvs)))
] forall a. Semigroup a => a -> a -> a
<> [Text]
caption forall a. Semigroup a => a -> a -> a
<> [Text]
head' forall a. Semigroup a => a -> a -> a
<> [Text]
bodies' forall a. Semigroup a => a -> a -> a
<> [Text]
foot' forall a. Semigroup a => a -> a -> a
<> [
Text
"|}"
]
tableHeadToMW :: PandocMonad m => Ann.TableHead -> MediaWikiWriter m [Text]
tableHeadToMW :: forall (m :: * -> *).
PandocMonad m =>
TableHead -> MediaWikiWriter m [Text]
tableHeadToMW (Ann.TableHead Attr
_ [HeaderRow]
rows) = forall (m :: * -> *).
PandocMonad m =>
[HeaderRow] -> MediaWikiWriter m [Text]
headerRowsToMW [HeaderRow]
rows
tableFootToMW :: PandocMonad m => Ann.TableFoot -> MediaWikiWriter m [Text]
(Ann.TableFoot Attr
_ [HeaderRow]
rows) = forall (m :: * -> *).
PandocMonad m =>
[HeaderRow] -> MediaWikiWriter m [Text]
headerRowsToMW [HeaderRow]
rows
tableBodyToMW :: PandocMonad m => Ann.TableBody -> MediaWikiWriter m [Text]
tableBodyToMW :: forall (m :: * -> *).
PandocMonad m =>
TableBody -> MediaWikiWriter m [Text]
tableBodyToMW (Ann.TableBody Attr
_ RowHeadColumns
_ [HeaderRow]
headerRows [BodyRow]
bodyRows) = do
[Text]
headerRows' <- forall (m :: * -> *).
PandocMonad m =>
[HeaderRow] -> MediaWikiWriter m [Text]
headerRowsToMW [HeaderRow]
headerRows
[Text]
bodyRows' <- forall (m :: * -> *).
PandocMonad m =>
[BodyRow] -> MediaWikiWriter m [Text]
bodyRowsToMW [BodyRow]
bodyRows
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Text]
headerRows' forall a. Semigroup a => a -> a -> a
<> [Text]
bodyRows'
headerRowsToMW :: PandocMonad m => [Ann.HeaderRow] -> MediaWikiWriter m [Text]
[HeaderRow]
rows = (\[[Text]]
x -> forall a. Monoid a => [a] -> a
mconcat [[Text]]
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
HeaderRow -> MediaWikiWriter m [Text]
headerRowToMW [HeaderRow]
rows
headerRowToMW :: PandocMonad m => Ann.HeaderRow -> MediaWikiWriter m [Text]
(Ann.HeaderRow Attr
attr RowNumber
_ [Cell]
cells) = do
[Text]
cells' <- (\[[Text]]
x -> forall a. Monoid a => [a] -> a
mconcat [[Text]]
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *).
PandocMonad m =>
Text -> Cell -> MediaWikiWriter m [Text]
cellToMW Text
"!") [Cell]
cells
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Text
"|-" forall a. Semigroup a => a -> a -> a
<> (forall a. HasChars a => Maybe Int -> Doc a -> a
render forall a. Maybe a
Nothing (forall a. HasChars a => Attr -> Doc a
htmlAttrs Attr
attr))] forall a. Semigroup a => a -> a -> a
<> [Text]
cells'
bodyRowsToMW :: PandocMonad m => [Ann.BodyRow] -> MediaWikiWriter m [Text]
bodyRowsToMW :: forall (m :: * -> *).
PandocMonad m =>
[BodyRow] -> MediaWikiWriter m [Text]
bodyRowsToMW [BodyRow]
rows = (\[[Text]]
x -> forall a. Monoid a => [a] -> a
mconcat [[Text]]
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
BodyRow -> MediaWikiWriter m [Text]
bodyRowToMW [BodyRow]
rows
bodyRowToMW :: PandocMonad m => Ann.BodyRow -> MediaWikiWriter m [Text]
bodyRowToMW :: forall (m :: * -> *).
PandocMonad m =>
BodyRow -> MediaWikiWriter m [Text]
bodyRowToMW (Ann.BodyRow Attr
attr RowNumber
_ [Cell]
headCells [Cell]
bodyCells) = do
[Text]
headCells' <- (\[[Text]]
x -> forall a. Monoid a => [a] -> a
mconcat [[Text]]
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *).
PandocMonad m =>
Text -> Cell -> MediaWikiWriter m [Text]
cellToMW Text
"!") [Cell]
headCells
[Text]
bodyCells' <- (\[[Text]]
x -> forall a. Monoid a => [a] -> a
mconcat [[Text]]
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *).
PandocMonad m =>
Text -> Cell -> MediaWikiWriter m [Text]
cellToMW Text
"|") [Cell]
bodyCells
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Text
"|-" forall a. Semigroup a => a -> a -> a
<> (forall a. HasChars a => Maybe Int -> Doc a -> a
render forall a. Maybe a
Nothing (forall a. HasChars a => Attr -> Doc a
htmlAttrs Attr
attr))] forall a. Semigroup a => a -> a -> a
<> [Text]
headCells' forall a. Semigroup a => a -> a -> a
<> [Text]
bodyCells'
cellToMW :: PandocMonad m => Text -> Ann.Cell -> MediaWikiWriter m [Text]
cellToMW :: forall (m :: * -> *).
PandocMonad m =>
Text -> Cell -> MediaWikiWriter m [Text]
cellToMW Text
marker (Ann.Cell (ColSpec
colSpec :| [ColSpec]
_) ColNumber
_ (Cell Attr
attr Alignment
align RowSpan
rowspan ColSpan
colspan [Block]
content)) = do
Text
content' <- forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [Block]
content
let (Text
ident,[Text]
classes,[(Text, Text)]
keyVals) = Attr
attr
let align' :: Alignment
align' = case Alignment
align of
Alignment
AlignDefault -> forall a b. (a, b) -> a
fst ColSpec
colSpec
Alignment
_ -> Alignment
align
let keyVals' :: [(Text, Text)]
keyVals' = case (Alignment -> Maybe Text
htmlAlignmentToString Alignment
align') of
Maybe Text
Nothing -> [(Text, Text)]
keyVals
Just Text
alignStr -> (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
htmlAddStyle (Text
"text-align", Text
alignStr) [(Text, Text)]
keyVals
let rowspan' :: [(Text, Text)]
rowspan' = case RowSpan
rowspan of
RowSpan Int
1 -> forall a. Monoid a => a
mempty
RowSpan Int
n -> [(Text
"rowspan", [Char] -> Text
T.pack(forall a. Show a => a -> [Char]
show Int
n))]
let colspan' :: [(Text, Text)]
colspan' = case ColSpan
colspan of
ColSpan Int
1 -> forall a. Monoid a => a
mempty
ColSpan Int
n -> [(Text
"colspan", [Char] -> Text
T.pack(forall a. Show a => a -> [Char]
show Int
n))]
let attrs' :: Text
attrs' = Text -> Text
addPipeIfNotEmpty (forall a. HasChars a => Maybe Int -> Doc a -> a
render forall a. Maybe a
Nothing (forall a. HasChars a => Attr -> Doc a
htmlAttrs (Text
ident, [Text]
classes, [(Text, Text)]
rowspan' forall a. Semigroup a => a -> a -> a
<> [(Text, Text)]
colspan' forall a. Semigroup a => a -> a -> a
<> [(Text, Text)]
keyVals')))
forall (m :: * -> *) a. Monad m => a -> m a
return [Text
marker forall a. Semigroup a => a -> a -> a
<> Text
attrs' forall a. Semigroup a => a -> a -> a
<> Text -> Text
addSpaceIfNotEmpty(Text
content')]
addPipeIfNotEmpty :: Text -> Text
addPipeIfNotEmpty :: Text -> Text
addPipeIfNotEmpty Text
f = if Text -> Bool
T.null Text
f then Text
f else Text
f forall a. Semigroup a => a -> a -> a
<> Text
"|"
addSpaceIfNotEmpty :: Text -> Text
addSpaceIfNotEmpty :: Text -> Text
addSpaceIfNotEmpty Text
f = if Text -> Bool
T.null Text
f then Text
f else Text
" " forall a. Semigroup a => a -> a -> a
<> Text
f
imageToMediaWiki :: PandocMonad m => Attr -> MediaWikiWriter m Text
imageToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
Attr -> MediaWikiWriter m Text
imageToMediaWiki Attr
attr = do
WriterOptions
opts <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> WriterOptions
stOptions
let (Text
_, [Text]
cls, [(Text, Text)]
_) = Attr
attr
toPx :: Maybe Dimension -> Maybe Text
toPx = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (WriterOptions -> Dimension -> Text
showInPixel WriterOptions
opts) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Dimension -> Maybe Dimension
checkPct
checkPct :: Maybe Dimension -> Maybe Dimension
checkPct (Just (Percent Double
_)) = forall a. Maybe a
Nothing
checkPct Maybe Dimension
maybeDim = Maybe Dimension
maybeDim
go :: Maybe a -> Maybe a -> a
go (Just a
w) Maybe a
Nothing = a
w forall a. Semigroup a => a -> a -> a
<> a
"px"
go (Just a
w) (Just a
h) = a
w forall a. Semigroup a => a -> a -> a
<> a
"x" forall a. Semigroup a => a -> a -> a
<> a
h forall a. Semigroup a => a -> a -> a
<> a
"px"
go Maybe a
Nothing (Just a
h) = a
"x" forall a. Semigroup a => a -> a -> a
<> a
h forall a. Semigroup a => a -> a -> a
<> a
"px"
go Maybe a
Nothing Maybe a
Nothing = a
""
dims :: Text
dims = forall {a}. (Semigroup a, IsString a) => Maybe a -> Maybe a -> a
go (Maybe Dimension -> Maybe Text
toPx forall a b. (a -> b) -> a -> b
$ Direction -> Attr -> Maybe Dimension
dimension Direction
Width Attr
attr) (Maybe Dimension -> Maybe Text
toPx forall a b. (a -> b) -> a -> b
$ Direction -> Attr -> Maybe Dimension
dimension Direction
Height Attr
attr)
classes :: Text
classes = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
cls
then Text
""
else Text
"class=" forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.unwords [Text]
cls
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
T.intercalate Text
"|" forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) [Text
dims, Text
classes]
blockListToMediaWiki :: PandocMonad m
=> [Block]
-> MediaWikiWriter m Text
blockListToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [Block]
blocks =
[Text] -> Text
vcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
Block -> MediaWikiWriter m Text
blockToMediaWiki [Block]
blocks
inlineListToMediaWiki :: PandocMonad m => [Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Text] -> Text
T.concat forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall (m :: * -> *).
PandocMonad m =>
Inline -> MediaWikiWriter m Text
inlineToMediaWiki forall a b. (a -> b) -> a -> b
$ [Inline] -> [Inline]
fixup [Inline]
lst
where
fixup :: [Inline] -> [Inline]
fixup [] = []
fixup (Str Text
t : Inline
x : [Inline]
xs)
| Bool -> Bool
not (Text -> Bool
T.null Text
t) Bool -> Bool -> Bool
&& Text -> Char
T.last Text
t forall a. Eq a => a -> a -> Bool
== Char
'['
, Inline -> Bool
isLinkOrImage Inline
x =
Text -> Inline
Str Text
t forall a. a -> [a] -> [a]
: Format -> Text -> Inline
RawInline (Text -> Format
Format Text
"mediawiki") Text
"<nowiki/>" forall a. a -> [a] -> [a]
: Inline
x forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
fixup [Inline]
xs
fixup (Inline
x:[Inline]
xs) = Inline
x forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
fixup [Inline]
xs
isLinkOrImage :: Inline -> Bool
isLinkOrImage Link{} = Bool
True
isLinkOrImage Image{} = Bool
True
isLinkOrImage Inline
_ = Bool
False
inlineToMediaWiki :: PandocMonad m => Inline -> MediaWikiWriter m Text
inlineToMediaWiki :: forall (m :: * -> *).
PandocMonad m =>
Inline -> MediaWikiWriter m Text
inlineToMediaWiki (Span Attr
attrs [Inline]
ils) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
ils
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. HasChars a => Maybe Int -> Doc a -> a
render forall a. Maybe a
Nothing (forall a. HasChars a => a -> Attr -> Doc a
tagWithAttrs Text
"span" Attr
attrs) forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"</span>"
inlineToMediaWiki (Emph [Inline]
lst) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"''" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"''"
inlineToMediaWiki (Underline [Inline]
lst) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<u>" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"</u>"
inlineToMediaWiki (Strong [Inline]
lst) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"'''" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"'''"
inlineToMediaWiki (Strikeout [Inline]
lst) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<s>" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"</s>"
inlineToMediaWiki (Superscript [Inline]
lst) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<sup>" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"</sup>"
inlineToMediaWiki (Subscript [Inline]
lst) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<sub>" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"</sub>"
inlineToMediaWiki (SmallCaps [Inline]
lst) = forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
inlineToMediaWiki (Quoted QuoteType
SingleQuote [Inline]
lst) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"\8216" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"\8217"
inlineToMediaWiki (Quoted QuoteType
DoubleQuote [Inline]
lst) = do
Text
contents <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"\8220" forall a. Semigroup a => a -> a -> a
<> Text
contents forall a. Semigroup a => a -> a -> a
<> Text
"\8221"
inlineToMediaWiki (Cite [Citation]
_ [Inline]
lst) = forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
lst
inlineToMediaWiki (Code Attr
_ Text
str) =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<code>" forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeText Text
str forall a. Semigroup a => a -> a -> a
<> Text
"</code>"
inlineToMediaWiki (Str Text
str) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Text
escapeText Text
str
inlineToMediaWiki (Math MathType
mt Text
str) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
Text
"<math display=\"" forall a. Semigroup a => a -> a -> a
<>
(if MathType
mt forall a. Eq a => a -> a -> Bool
== MathType
DisplayMath then Text
"block" else Text
"inline") forall a. Semigroup a => a -> a -> a
<>
Text
"\">" forall a. Semigroup a => a -> a -> a
<> Text
str forall a. Semigroup a => a -> a -> a
<> Text
"</math>"
inlineToMediaWiki il :: Inline
il@(RawInline Format
f Text
str)
| Format
f forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"mediawiki" = forall (m :: * -> *) a. Monad m => a -> m a
return Text
str
| Format
f forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"html" = forall (m :: * -> *) a. Monad m => a -> m a
return Text
str
| Bool
otherwise = Text
"" forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (Inline -> LogMessage
InlineNotRendered Inline
il)
inlineToMediaWiki Inline
LineBreak = forall (m :: * -> *) a. Monad m => a -> m a
return Text
"<br />\n"
inlineToMediaWiki Inline
SoftBreak = do
WrapOption
wrapText <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (WriterOptions -> WrapOption
writerWrapText forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterState -> WriterOptions
stOptions)
[Char]
listlevel <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks WriterReader -> [Char]
listLevel
case WrapOption
wrapText of
WrapOption
WrapAuto -> forall (m :: * -> *) a. Monad m => a -> m a
return Text
" "
WrapOption
WrapNone -> forall (m :: * -> *) a. Monad m => a -> m a
return Text
" "
WrapOption
WrapPreserve -> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
listlevel
then forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\n"
else forall (m :: * -> *) a. Monad m => a -> m a
return Text
" "
inlineToMediaWiki Inline
Space = forall (m :: * -> *) a. Monad m => a -> m a
return Text
" "
inlineToMediaWiki (Link Attr
_ [Inline]
txt (Text
src, Text
_)) = do
Text
label <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki ([Inline] -> [Inline]
removeLinks [Inline]
txt)
case [Inline]
txt of
[Str Text
s] | Text -> Bool
isURI Text
src Bool -> Bool -> Bool
&& Text -> Text
escapeURI Text
s forall a. Eq a => a -> a -> Bool
== Text
src -> forall (m :: * -> *) a. Monad m => a -> m a
return Text
src
[Inline]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ if Text -> Bool
isURI Text
src
then Text
"[" forall a. Semigroup a => a -> a -> a
<> Text
src forall a. Semigroup a => a -> a -> a
<> Text
" " forall a. Semigroup a => a -> a -> a
<> Text
label forall a. Semigroup a => a -> a -> a
<> Text
"]"
else
if Text
src forall a. Eq a => a -> a -> Bool
== Text
label
then Text
"[[" forall a. Semigroup a => a -> a -> a
<> Text
src' forall a. Semigroup a => a -> a -> a
<> Text
"]]"
else Text
"[[" forall a. Semigroup a => a -> a -> a
<> Text
src' forall a. Semigroup a => a -> a -> a
<> Text
"|" forall a. Semigroup a => a -> a -> a
<> Text
label forall a. Semigroup a => a -> a -> a
<> Text
"]]"
where src' :: Text
src' = forall a. a -> Maybe a -> a
fromMaybe Text
src forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Text
T.stripPrefix Text
"/" Text
src
inlineToMediaWiki (Image Attr
attr [Inline]
alt (Text
source, Text
tit)) = do
Text
img <- forall (m :: * -> *).
PandocMonad m =>
Attr -> MediaWikiWriter m Text
imageToMediaWiki Attr
attr
Text
alt' <- forall (m :: * -> *).
PandocMonad m =>
[Inline] -> MediaWikiWriter m Text
inlineListToMediaWiki [Inline]
alt
let txt :: Text
txt = if Text -> Bool
T.null Text
alt'
then if Text -> Bool
T.null Text
tit
then Text
""
else Text
tit
else Text
alt'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"[[" forall a. Semigroup a => a -> a -> a
<>
Text -> [Text] -> Text
T.intercalate Text
"|"
(forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null)
[ Text
"File:" forall a. Semigroup a => a -> a -> a
<> Text
source
, Text
img
, Text
txt
]) forall a. Semigroup a => a -> a -> a
<> Text
"]]"
inlineToMediaWiki (Note [Block]
contents) = do
Text
contents' <- forall (m :: * -> *).
PandocMonad m =>
[Block] -> MediaWikiWriter m Text
blockListToMediaWiki [Block]
contents
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\WriterState
s -> WriterState
s { stNotes :: Bool
stNotes = Bool
True })
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
"<ref>" forall a. Semigroup a => a -> a -> a
<> Text -> Text
stripTrailingNewlines Text
contents' forall a. Semigroup a => a -> a -> a
<> Text
"</ref>"
removeLinks :: [Inline] -> [Inline]
removeLinks :: [Inline] -> [Inline]
removeLinks = forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
go
where
go :: Inline -> Inline
go (Link Attr
_ [Inline]
ils (Text, Text)
_) = [Inline] -> Inline
SmallCaps [Inline]
ils
go Inline
x = Inline
x
highlightingLangs :: Set.Set Text
highlightingLangs :: Set Text
highlightingLangs = forall a. Ord a => [a] -> Set a
Set.fromList [
Text
"abap",
Text
"abl",
Text
"abnf",
Text
"aconf",
Text
"actionscript",
Text
"actionscript3",
Text
"ada",
Text
"ada2005",
Text
"ada95",
Text
"adl",
Text
"agda",
Text
"ahk",
Text
"alloy",
Text
"ambienttalk",
Text
"ambienttalk/2",
Text
"antlr",
Text
"antlr-actionscript",
Text
"antlr-as",
Text
"antlr-c#",
Text
"antlr-cpp",
Text
"antlr-csharp",
Text
"antlr-java",
Text
"antlr-objc",
Text
"antlr-perl",
Text
"antlr-python",
Text
"antlr-rb",
Text
"antlr-ruby",
Text
"apache",
Text
"apacheconf",
Text
"apl",
Text
"applescript",
Text
"arduino",
Text
"arexx",
Text
"as",
Text
"as3",
Text
"asm",
Text
"aspectj",
Text
"aspx-cs",
Text
"aspx-vb",
Text
"asy",
Text
"asymptote",
Text
"at",
Text
"autohotkey",
Text
"autoit",
Text
"awk",
Text
"b3d",
Text
"basemake",
Text
"bash",
Text
"basic",
Text
"bat",
Text
"batch",
Text
"bbcode",
Text
"because",
Text
"befunge",
Text
"bf",
Text
"blitzbasic",
Text
"blitzmax",
Text
"bmax",
Text
"bnf",
Text
"boo",
Text
"boogie",
Text
"bplus",
Text
"brainfuck",
Text
"bro",
Text
"bsdmake",
Text
"bugs",
Text
"c",
Text
"c#",
Text
"c++",
Text
"c++-objdumb",
Text
"c-objdump",
Text
"ca65",
Text
"cadl",
Text
"camkes",
Text
"cbmbas",
Text
"ceylon",
Text
"cf3",
Text
"cfc",
Text
"cfengine3",
Text
"cfg",
Text
"cfm",
Text
"cfs",
Text
"chai",
Text
"chaiscript",
Text
"chapel",
Text
"cheetah",
Text
"chpl",
Text
"cirru",
Text
"cl",
Text
"clay",
Text
"clipper",
Text
"clj",
Text
"cljs",
Text
"clojure",
Text
"clojurescript",
Text
"cmake",
Text
"cobol",
Text
"cobolfree",
Text
"coffee",
Text
"coffee-script",
Text
"coffeescript",
Text
"common-lisp",
Text
"componentpascal",
Text
"console",
Text
"control",
Text
"coq",
Text
"cp",
Text
"cpp",
Text
"cpp-objdump",
Text
"cpsa",
Text
"crmsh",
Text
"croc",
Text
"cry",
Text
"cryptol",
Text
"csh",
Text
"csharp",
Text
"csound",
Text
"csound-csd",
Text
"csound-document",
Text
"csound-orc",
Text
"csound-sco",
Text
"csound-score",
Text
"css",
Text
"css+django",
Text
"css+erb",
Text
"css+genshi",
Text
"css+genshitext",
Text
"css+jinja",
Text
"css+lasso",
Text
"css+mako",
Text
"css+mozpreproc",
Text
"css+myghty",
Text
"css+php",
Text
"css+ruby",
Text
"css+smarty",
Text
"cu",
Text
"cucumber",
Text
"cuda",
Text
"cxx-objdump",
Text
"cypher",
Text
"cython",
Text
"d",
Text
"d-objdump",
Text
"dart",
Text
"debcontrol",
Text
"debsources",
Text
"delphi",
Text
"dg",
Text
"diff",
Text
"django",
Text
"docker",
Text
"dockerfile",
Text
"dosbatch",
Text
"doscon",
Text
"dosini",
Text
"dpatch",
Text
"dtd",
Text
"duby",
Text
"duel",
Text
"dylan",
Text
"dylan-console",
Text
"dylan-lid",
Text
"dylan-repl",
Text
"earl-grey",
Text
"earlgrey",
Text
"easytrieve",
Text
"ebnf",
Text
"ec",
Text
"ecl",
Text
"eg",
Text
"eiffel",
Text
"elisp",
Text
"elixir",
Text
"elm",
Text
"emacs",
Text
"erb",
Text
"erl",
Text
"erlang",
Text
"evoque",
Text
"ex",
Text
"exs",
Text
"ezhil",
Text
"f#",
Text
"factor",
Text
"fan",
Text
"fancy",
Text
"felix",
Text
"fish",
Text
"fishshell",
Text
"flx",
Text
"fortran",
Text
"fortranfixed",
Text
"foxpro",
Text
"fsharp",
Text
"fy",
Text
"gap",
Text
"gas",
Text
"gawk",
Text
"genshi",
Text
"genshitext",
Text
"gherkin",
Text
"glsl",
Text
"gnuplot",
Text
"go",
Text
"golo",
Text
"gooddata-cl",
Text
"gosu",
Text
"groff",
Text
"groovy",
Text
"gst",
Text
"haml",
Text
"handlebars",
Text
"haskell",
Text
"haxe",
Text
"haxeml",
Text
"hexdump",
Text
"hs",
Text
"html",
Text
"html+cheetah",
Text
"html+django",
Text
"html+erb",
Text
"html+evoque",
Text
"html+genshi",
Text
"html+handlebars",
Text
"html+jinja",
Text
"html+kid",
Text
"html+lasso",
Text
"html+mako",
Text
"html+myghty",
Text
"html+php",
Text
"html+ruby",
Text
"html+smarty",
Text
"html+spitfire",
Text
"html+twig",
Text
"html+velocity",
Text
"htmlcheetah",
Text
"htmldjango",
Text
"http",
Text
"hx",
Text
"hxml",
Text
"hxsl",
Text
"hy",
Text
"hybris",
Text
"hylang",
Text
"i6",
Text
"i6t",
Text
"i7",
Text
"idl",
Text
"idl4",
Text
"idr",
Text
"idris",
Text
"iex",
Text
"igor",
Text
"igorpro",
Text
"ik",
Text
"inform6",
Text
"inform7",
Text
"ini",
Text
"io",
Text
"ioke",
Text
"irb",
Text
"irc",
Text
"isabelle",
Text
"j",
Text
"jade",
Text
"jags",
Text
"jasmin",
Text
"jasminxt",
Text
"java",
Text
"javascript",
Text
"javascript+cheetah",
Text
"javascript+django",
Text
"javascript+erb",
Text
"javascript+genshi",
Text
"javascript+genshitext",
Text
"javascript+jinja",
Text
"javascript+lasso",
Text
"javascript+mako",
Text
"javascript+mozpreproc",
Text
"javascript+myghty",
Text
"javascript+php",
Text
"javascript+ruby",
Text
"javascript+smarty",
Text
"javascript+spitfire",
Text
"jbst",
Text
"jcl",
Text
"jinja",
Text
"jl",
Text
"jlcon",
Text
"jproperties",
Text
"js",
Text
"js+cheetah",
Text
"js+django",
Text
"js+erb",
Text
"js+genshi",
Text
"js+genshitext",
Text
"js+jinja",
Text
"js+lasso",
Text
"js+mako",
Text
"js+myghty",
Text
"js+php",
Text
"js+ruby",
Text
"js+smarty",
Text
"js+spitfire",
Text
"json",
Text
"json-ld",
Text
"jsonld",
Text
"jsonml+bst",
Text
"jsp",
Text
"julia",
Text
"kal",
Text
"kconfig",
Text
"kernel-config",
Text
"kid",
Text
"koka",
Text
"kotlin",
Text
"ksh",
Text
"lagda",
Text
"lasso",
Text
"lassoscript",
Text
"latex",
Text
"lcry",
Text
"lcryptol",
Text
"lean",
Text
"less",
Text
"lhaskell",
Text
"lhs",
Text
"lid",
Text
"lidr",
Text
"lidris",
Text
"lighttpd",
Text
"lighty",
Text
"limbo",
Text
"linux-config",
Text
"liquid",
Text
"lisp",
Text
"literate-agda",
Text
"literate-cryptol",
Text
"literate-haskell",
Text
"literate-idris",
Text
"live-script",
Text
"livescript",
Text
"llvm",
Text
"logos",
Text
"logtalk",
Text
"lsl",
Text
"lua",
Text
"m2",
Text
"make",
Text
"makefile",
Text
"mako",
Text
"man",
Text
"maql",
Text
"mask",
Text
"mason",
Text
"mathematica",
Text
"matlab",
Text
"matlabsession",
Text
"mawk",
Text
"menuconfig",
Text
"mf",
Text
"minid",
Text
"mma",
Text
"modelica",
Text
"modula2",
Text
"moin",
Text
"monkey",
Text
"moo",
Text
"moocode",
Text
"moon",
Text
"moonscript",
Text
"mozhashpreproc",
Text
"mozpercentpreproc",
Text
"mq4",
Text
"mq5",
Text
"mql",
Text
"mql4",
Text
"mql5",
Text
"msc",
Text
"mscgen",
Text
"mupad",
Text
"mxml",
Text
"myghty",
Text
"mysql",
Text
"nasm",
Text
"nawk",
Text
"nb",
Text
"nemerle",
Text
"nesc",
Text
"newlisp",
Text
"newspeak",
Text
"nginx",
Text
"nim",
Text
"nimrod",
Text
"nit",
Text
"nix",
Text
"nixos",
Text
"nroff",
Text
"nsh",
Text
"nsi",
Text
"nsis",
Text
"numpy",
Text
"obj-c",
Text
"obj-c++",
Text
"obj-j",
Text
"objc",
Text
"objc++",
Text
"objdump",
Text
"objdump-nasm",
Text
"objective-c",
Text
"objective-c++",
Text
"objective-j",
Text
"objectivec",
Text
"objectivec++",
Text
"objectivej",
Text
"objectpascal",
Text
"objj",
Text
"ocaml",
Text
"octave",
Text
"odin",
Text
"ooc",
Text
"opa",
Text
"openbugs",
Text
"openedge",
Text
"pacmanconf",
Text
"pan",
Text
"parasail",
Text
"pas",
Text
"pascal",
Text
"pawn",
Text
"pcmk",
Text
"perl",
Text
"perl6",
Text
"php",
Text
"php3",
Text
"php4",
Text
"php5",
Text
"pig",
Text
"pike",
Text
"pkgconfig",
Text
"pl",
Text
"pl6",
Text
"plpgsql",
Text
"po",
Text
"posh",
Text
"postgres",
Text
"postgres-console",
Text
"postgresql",
Text
"postgresql-console",
Text
"postscr",
Text
"postscript",
Text
"pot",
Text
"pov",
Text
"powershell",
Text
"praat",
Text
"progress",
Text
"prolog",
Text
"properties",
Text
"proto",
Text
"protobuf",
Text
"ps1",
Text
"ps1con",
Text
"psm1",
Text
"psql",
Text
"puppet",
Text
"py",
Text
"py3",
Text
"py3tb",
Text
"pycon",
Text
"pypy",
Text
"pypylog",
Text
"pyrex",
Text
"pytb",
Text
"python",
Text
"python3",
Text
"pyx",
Text
"qbasic",
Text
"qbs",
Text
"qml",
Text
"qvt",
Text
"qvto",
Text
"r",
Text
"racket",
Text
"ragel",
Text
"ragel-c",
Text
"ragel-cpp",
Text
"ragel-d",
Text
"ragel-em",
Text
"ragel-java",
Text
"ragel-objc",
Text
"ragel-rb",
Text
"ragel-ruby",
Text
"raw",
Text
"rb",
Text
"rbcon",
Text
"rconsole",
Text
"rd",
Text
"rebol",
Text
"red",
Text
"red/system",
Text
"redcode",
Text
"registry",
Text
"resource",
Text
"resourcebundle",
Text
"rest",
Text
"restructuredtext",
Text
"rexx",
Text
"rhtml",
Text
"rkt",
Text
"roboconf-graph",
Text
"roboconf-instances",
Text
"robotframework",
Text
"rout",
Text
"rql",
Text
"rsl",
Text
"rst",
Text
"rts",
Text
"ruby",
Text
"rust",
Text
"s",
Text
"sage",
Text
"salt",
Text
"sass",
Text
"sc",
Text
"scala",
Text
"scaml",
Text
"scheme",
Text
"scilab",
Text
"scm",
Text
"scss",
Text
"sh",
Text
"shell",
Text
"shell-session",
Text
"shen",
Text
"slim",
Text
"sls",
Text
"smali",
Text
"smalltalk",
Text
"smarty",
Text
"sml",
Text
"snobol",
Text
"sources.list",
Text
"sourceslist",
Text
"sp",
Text
"sparql",
Text
"spec",
Text
"spitfire",
Text
"splus",
Text
"sql",
Text
"sqlite3",
Text
"squeak",
Text
"squid",
Text
"squid.conf",
Text
"squidconf",
Text
"ssp",
Text
"st",
Text
"stan",
Text
"supercollider",
Text
"sv",
Text
"swift",
Text
"swig",
Text
"systemverilog",
Text
"tads3",
Text
"tap",
Text
"tcl",
Text
"tcsh",
Text
"tcshcon",
Text
"tea",
Text
"termcap",
Text
"terminfo",
Text
"terraform",
Text
"tex",
Text
"text",
Text
"tf",
Text
"thrift",
Text
"todotxt",
Text
"trac-wiki",
Text
"trafficscript",
Text
"treetop",
Text
"ts",
Text
"turtle",
Text
"twig",
Text
"typescript",
Text
"udiff",
Text
"urbiscript",
Text
"v",
Text
"vala",
Text
"vapi",
Text
"vb.net",
Text
"vbnet",
Text
"vctreestatus",
Text
"velocity",
Text
"verilog",
Text
"vfp",
Text
"vgl",
Text
"vhdl",
Text
"vim",
Text
"winbatch",
Text
"winbugs",
Text
"x10",
Text
"xbase",
Text
"xml",
Text
"xml+cheetah",
Text
"xml+django",
Text
"xml+erb",
Text
"xml+evoque",
Text
"xml+genshi",
Text
"xml+jinja",
Text
"xml+kid",
Text
"xml+lasso",
Text
"xml+mako",
Text
"xml+myghty",
Text
"xml+php",
Text
"xml+ruby",
Text
"xml+smarty",
Text
"xml+spitfire",
Text
"xml+velocity",
Text
"xq",
Text
"xql",
Text
"xqm",
Text
"xquery",
Text
"xqy",
Text
"xslt",
Text
"xten",
Text
"xtend",
Text
"xul+mozpreproc",
Text
"yaml",
Text
"yaml+jinja",
Text
"zephir" ]