aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/PandocModule.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/PandocModule.hs')
-rw-r--r--src/Text/Pandoc/Lua/PandocModule.hs74
1 files changed, 72 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Lua/PandocModule.hs b/src/Text/Pandoc/Lua/PandocModule.hs
index 87d1fa6b9..d0c78f562 100644
--- a/src/Text/Pandoc/Lua/PandocModule.hs
+++ b/src/Text/Pandoc/Lua/PandocModule.hs
@@ -28,11 +28,25 @@ Pandoc module for lua.
module Text.Pandoc.Lua.PandocModule ( pushPandocModule ) where
import Data.ByteString.Char8 ( unpack )
-import Scripting.Lua ( LuaState, call)
+import Data.Default ( Default(..) )
+import Scripting.Lua ( LuaState, call, newtable, push, pushhsfunction, rawset)
+import Text.Pandoc.Class hiding ( readDataFile )
+import Text.Pandoc.Definition ( Pandoc(..), Block(..) )
import Text.Pandoc.Lua.Compat ( loadstring )
+import Text.Pandoc.Lua.StackInstances ()
+import Text.Pandoc.Readers.DocBook ( readDocBook )
+import Text.Pandoc.Readers.HTML ( readHtml )
+import Text.Pandoc.Readers.LaTeX ( readLaTeX )
+import Text.Pandoc.Readers.Native ( readNative )
+import Text.Pandoc.Readers.Markdown ( readMarkdown )
+import Text.Pandoc.Readers.MediaWiki ( readMediaWiki )
+import Text.Pandoc.Readers.Org ( readOrg )
+import Text.Pandoc.Readers.RST ( readRST )
+import Text.Pandoc.Readers.Textile ( readTextile )
+import Text.Pandoc.Readers.TWiki ( readTWiki )
+import Text.Pandoc.Readers.Txt2Tags ( readTxt2Tags )
import Text.Pandoc.Shared ( readDataFile )
-
-- | Push the "pandoc" on the lua stack.
pushPandocModule :: LuaState -> IO ()
pushPandocModule lua = do
@@ -42,7 +56,63 @@ pushPandocModule lua = do
then return ()
else do
call lua 0 1
+ push lua "reader"
+ pushReadersModule lua readers
+ rawset lua (-3)
+
+readers :: [(String, String -> PandocIO Pandoc)]
+readers =
+ [ ("docbook", readDocBook def)
+ , ("html", readHtml def)
+ , ("latex", readLaTeX def)
+ , ("native", readNative def)
+ , ("markdown", readMarkdown def)
+ , ("mediawiki", readMediaWiki def)
+ , ("org", readOrg def)
+ , ("rst", readRST def)
+ , ("textile", readTextile def)
+ , ("twiki", readTWiki def)
+ , ("txt2tags", readTxt2Tags def)
+ ]
-- | Get the string representation of the pandoc module
pandocModuleScript :: IO String
pandocModuleScript = unpack <$> readDataFile Nothing "pandoc.lua"
+
+-- | Push a lua table containing readers of the given formats.
+pushReadersModule :: LuaState
+ -> [(String, String -> PandocIO Pandoc)]
+ -> IO ()
+pushReadersModule lua readerFns = do
+ newtable lua
+ mapM_ (uncurry $ addReaderTable) readerFns
+ where
+ addReaderTable :: String
+ -> (String -> PandocIO Pandoc)
+ -> IO ()
+ addReaderTable formatName readerFn = do
+ let readDoc :: String -> IO Pandoc
+ readDoc s = do
+ res <- runIO $ readerFn s
+ case res of
+ (Left x) -> error (show x)
+ (Right x) -> return x
+ let readBlock :: String -> IO Block
+ readBlock s = do
+ Pandoc _ blks <- readDoc s
+ return $ case blks of
+ x:_ -> x
+ _ -> Null
+ -- Push table containing all functions for this format
+ push lua formatName
+ newtable lua
+ -- set document-reading function
+ push lua "read_doc"
+ pushhsfunction lua readDoc
+ rawset lua (-3)
+ -- set block-reading function
+ push lua "read_block"
+ pushhsfunction lua readBlock
+ rawset lua (-3)
+ -- store table in readers module
+ rawset lua (-3)