aboutsummaryrefslogtreecommitdiff
path: root/plugins
diff options
context:
space:
mode:
Diffstat (limited to 'plugins')
-rw-r--r--plugins/CapitalizeEmphasisPlugin.hs14
-rw-r--r--plugins/DotPlugin.hs30
-rw-r--r--plugins/IncludeFilePlugin.hs19
-rw-r--r--plugins/ListLinksPlugin.hs15
-rw-r--r--plugins/WordPressPlugin.hs10
5 files changed, 88 insertions, 0 deletions
diff --git a/plugins/CapitalizeEmphasisPlugin.hs b/plugins/CapitalizeEmphasisPlugin.hs
new file mode 100644
index 000000000..31cb4403a
--- /dev/null
+++ b/plugins/CapitalizeEmphasisPlugin.hs
@@ -0,0 +1,14 @@
+module CapitalizeEmphasisPlugin (transform) where
+import Text.Pandoc
+import Data.Char (toUpper)
+
+-- This plugin changes emphasized text into CAPITALIZED TEXT.
+
+transform :: [Inline] -> [Inline]
+transform (Emph x : ys) = processIn capStr x ++ transform ys
+transform (x : ys) = x : transform ys
+transform [] = []
+
+capStr :: Inline -> Inline
+capStr (Str x) = Str (map toUpper x)
+capStr x = x
diff --git a/plugins/DotPlugin.hs b/plugins/DotPlugin.hs
new file mode 100644
index 000000000..db1a02e1c
--- /dev/null
+++ b/plugins/DotPlugin.hs
@@ -0,0 +1,30 @@
+module DotPlugin (transform) where
+import Text.Pandoc
+import Text.Pandoc.Shared
+import System.Process (readProcess)
+import Data.Char (ord)
+-- from the utf8-string package on HackageDB:
+import Data.ByteString.Lazy.UTF8 (fromString)
+-- from the SHA package on HackageDB:
+import Data.Digest.Pure.SHA
+
+-- This plugin allows you to include a graphviz "dot" diagram
+-- in a document like this:
+--
+-- ~~~ {.dot name="diagram1"}
+-- digraph G {Hello->World}
+-- ~~~
+
+transform :: Block -> IO Block
+transform (CodeBlock (id, classes, namevals) contents) | "dot" `elem` classes = do
+ let (name, outfile) = case lookup "name" namevals of
+ Just fn -> ([Str fn], fn ++ ".png")
+ Nothing -> ([], uniqueName contents ++ ".png")
+ result <- readProcess "dot" ["-Tpng"] contents
+ writeFile outfile result
+ return $ Para [Image name (outfile, "")]
+transform x = return x
+
+-- | Generate a unique filename given the file's contents.
+uniqueName :: String -> String
+uniqueName = showDigest . sha1 . fromString
diff --git a/plugins/IncludeFilePlugin.hs b/plugins/IncludeFilePlugin.hs
new file mode 100644
index 000000000..40a8ce34d
--- /dev/null
+++ b/plugins/IncludeFilePlugin.hs
@@ -0,0 +1,19 @@
+module IncludeFilePlugin (transform) where
+import Text.Pandoc
+import Text.Pandoc.Shared
+import Control.Monad
+
+-- This plugin allows you to include the contents of an
+-- external file in a delimited code block like this:
+--
+-- ~~~ {include="filename"}
+-- ~~~
+--
+-- Trailing newlines are trimmed.
+
+transform :: Block -> IO Block
+transform cb@(CodeBlock (id, classes, namevals) contents) =
+ case lookup "include" namevals of
+ Just f -> return . (CodeBlock (id, classes, namevals) . stripTrailingNewlines) =<< readFile f
+ Nothing -> return cb
+transform x = return x
diff --git a/plugins/ListLinksPlugin.hs b/plugins/ListLinksPlugin.hs
new file mode 100644
index 000000000..88c1553b1
--- /dev/null
+++ b/plugins/ListLinksPlugin.hs
@@ -0,0 +1,15 @@
+module ListLinksPlugin (transform) where
+import Text.Pandoc
+
+-- This plugin returns an empty document and prints a list
+-- of the URLs linked to in the source document.
+
+transform :: Pandoc -> IO Pandoc
+transform p = do
+ let urls = queryIn findURLs p
+ putStrLn $ unlines urls
+ return $ Pandoc (Meta [] [] []) []
+
+findURLs :: Inline -> [String]
+findURLs (Link label (url, title)) = [url]
+findURLs x = []
diff --git a/plugins/WordPressPlugin.hs b/plugins/WordPressPlugin.hs
new file mode 100644
index 000000000..85b7ca72b
--- /dev/null
+++ b/plugins/WordPressPlugin.hs
@@ -0,0 +1,10 @@
+module WordPressPlugin (transform) where
+import Text.Pandoc
+
+-- This plugin (when used with -m) prints LaTeX math in the
+-- format required by WordPress blogs. $e=mc^2$ becomes
+-- $LaTeX e=mc^2$.
+
+transform :: Inline -> Inline
+transform (Math x y) = Math x $ "LaTeX " ++ y
+transform x = x