aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module/Pandoc.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Module/Pandoc.hs')
-rw-r--r--src/Text/Pandoc/Lua/Module/Pandoc.hs52
1 files changed, 29 insertions, 23 deletions
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index 3886568b7..5c14b3a30 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -2,7 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.Pandoc
- Copyright : Copyright © 2017-2020 Albert Krewinkel
+ Copyright : Copyright © 2017-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -14,6 +14,7 @@ module Text.Pandoc.Lua.Module.Pandoc
( pushModule
) where
+import Prelude hiding (read)
import Control.Monad (when)
import Control.Monad.Except (throwError)
import Data.Default (Default (..))
@@ -22,10 +23,12 @@ import Foreign.Lua (Lua, NumResults, Optional, Peekable, Pushable)
import System.Exit (ExitCode (..))
import Text.Pandoc.Class.PandocIO (runIO)
import Text.Pandoc.Definition (Block, Inline)
-import Text.Pandoc.Lua.Filter (walkInlines, walkBlocks, LuaFilter, SingletonsList (..))
+import Text.Pandoc.Lua.Filter (LuaFilter, SingletonsList (..), walkInlines,
+ walkInlineLists, walkBlocks, walkBlockLists)
import Text.Pandoc.Lua.Marshaling ()
+import Text.Pandoc.Lua.Marshaling.List (List (..))
import Text.Pandoc.Lua.PandocLua (PandocLua, addFunction, liftPandocLua,
- loadScriptFromDataDir)
+ loadDefaultModule)
import Text.Pandoc.Walk (Walkable)
import Text.Pandoc.Options (ReaderOptions (readerExtensions))
import Text.Pandoc.Process (pipeProcess)
@@ -38,30 +41,33 @@ import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.Lua.Util as LuaUtil
import Text.Pandoc.Error
--- | Push the "pandoc" on the lua stack. Requires the `list` module to be
--- loaded.
+-- | Push the "pandoc" package to the Lua stack. Requires the `List`
+-- module to be loadable.
pushModule :: PandocLua NumResults
pushModule = do
- loadScriptFromDataDir "pandoc.lua"
- addFunction "read" readDoc
- addFunction "pipe" pipeFn
- addFunction "walk_block" walkBlock
- addFunction "walk_inline" walkInline
+ loadDefaultModule "pandoc"
+ addFunction "read" read
+ addFunction "pipe" pipe
+ addFunction "walk_block" walk_block
+ addFunction "walk_inline" walk_inline
return 1
walkElement :: (Walkable (SingletonsList Inline) a,
- Walkable (SingletonsList Block) a)
+ Walkable (SingletonsList Block) a,
+ Walkable (List Inline) a,
+ Walkable (List Block) a)
=> a -> LuaFilter -> PandocLua a
-walkElement x f = liftPandocLua $ walkInlines f x >>= walkBlocks f
+walkElement x f = liftPandocLua $
+ walkInlines f x >>= walkInlineLists f >>= walkBlocks f >>= walkBlockLists f
-walkInline :: Inline -> LuaFilter -> PandocLua Inline
-walkInline = walkElement
+walk_inline :: Inline -> LuaFilter -> PandocLua Inline
+walk_inline = walkElement
-walkBlock :: Block -> LuaFilter -> PandocLua Block
-walkBlock = walkElement
+walk_block :: Block -> LuaFilter -> PandocLua Block
+walk_block = walkElement
-readDoc :: T.Text -> Optional T.Text -> PandocLua NumResults
-readDoc content formatSpecOrNil = liftPandocLua $ do
+read :: T.Text -> Optional T.Text -> PandocLua NumResults
+read content formatSpecOrNil = liftPandocLua $ do
let formatSpec = fromMaybe "markdown" (Lua.fromOptional formatSpecOrNil)
res <- Lua.liftIO . runIO $
getReader formatSpec >>= \(rdr,es) ->
@@ -79,11 +85,11 @@ readDoc content formatSpecOrNil = liftPandocLua $ do
Left e -> Lua.raiseError $ show e
-- | Pipes input through a command.
-pipeFn :: String
- -> [String]
- -> BL.ByteString
- -> PandocLua NumResults
-pipeFn command args input = liftPandocLua $ do
+pipe :: String -- ^ path to executable
+ -> [String] -- ^ list of arguments
+ -> BL.ByteString -- ^ input passed to process via stdin
+ -> PandocLua NumResults
+pipe command args input = liftPandocLua $ do
(ec, output) <- Lua.liftIO $ pipeProcess Nothing command args input
case ec of
ExitSuccess -> 1 <$ Lua.push output