aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-11-05 22:10:29 -0700
committerGitHub <noreply@github.com>2021-11-05 22:10:29 -0700
commitee2f0021f9b59f0bca6eabf4884641da7a09e21d (patch)
treef29d5325d1d89c736093534d27b62c98a674df57 /src/Text/Pandoc/Readers
parentbac6ae9607582233336984c30bba3c586eba6844 (diff)
downloadpandoc-ee2f0021f9b59f0bca6eabf4884641da7a09e21d.tar.gz
Add interface for custom readers written in Lua. (#7671)
New module Text.Pandoc.Readers.Custom, exporting readCustom [API change]. Users can now do `-f myreader.lua` and pandoc will treat the script myreader.lua as a custom reader, which parses an input string to a pandoc AST, using the pandoc module defined for Lua filters. A sample custom reader can be found in data/reader.lua. Closes #7669.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/Custom.hs55
1 files changed, 55 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Readers/Custom.hs b/src/Text/Pandoc/Readers/Custom.hs
new file mode 100644
index 000000000..83d82a9cc
--- /dev/null
+++ b/src/Text/Pandoc/Readers/Custom.hs
@@ -0,0 +1,55 @@
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
+{- |
+ Module : Text.Pandoc.Readers.Custom
+ Copyright : Copyright (C) 2021 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <jgm@berkeley.edu>
+ Stability : alpha
+ Portability : portable
+
+Supports custom parsers written in Lua which produce a Pandoc AST.
+-}
+module Text.Pandoc.Readers.Custom ( readCustom ) where
+import Control.Exception
+import Control.Monad (when)
+import Data.Text (Text)
+import HsLua as Lua hiding (Operation (Div), render)
+import HsLua.Class.Peekable (PeekError)
+import Control.Monad.IO.Class (MonadIO)
+import Text.Pandoc.Definition
+import Text.Pandoc.Lua (Global (..), runLua, setGlobals)
+import Text.Pandoc.Lua.Util (dofileWithTraceback)
+import Text.Pandoc.Options
+import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Sources (ToSources(..), sourcesToText)
+
+-- | Convert custom markup to Pandoc.
+readCustom :: (PandocMonad m, MonadIO m, ToSources s)
+ => FilePath -> ReaderOptions -> s -> m Pandoc
+readCustom luaFile opts sources = do
+ let input = sourcesToText $ toSources sources
+ let globals = [ PANDOC_SCRIPT_FILE luaFile
+ , PANDOC_READER_OPTIONS opts
+ ]
+ res <- runLua $ do
+ setGlobals globals
+ stat <- dofileWithTraceback luaFile
+ -- check for error in lua script (later we'll change the return type
+ -- to handle this more gracefully):
+ when (stat /= Lua.OK)
+ Lua.throwErrorAsException
+ parseCustom input
+ case res of
+ Left msg -> throw msg
+ Right doc -> return doc
+
+parseCustom :: forall e. PeekError e
+ => Text
+ -> LuaE e Pandoc
+parseCustom = invoke @e "Reader"
+