Lua filters: use same function names in Haskell and Lua
This commit is contained in:
parent
57e56ed55c
commit
a5169f68b2
3 changed files with 31 additions and 28 deletions
|
@ -60,6 +60,7 @@
|
|||
- Text.Pandoc.Citeproc
|
||||
- Text.Pandoc.Extensions
|
||||
- Text.Pandoc.Lua.Marshaling.Version
|
||||
- Text.Pandoc.Lua.Module.Pandoc
|
||||
- Text.Pandoc.Lua.Module.Utils
|
||||
- Text.Pandoc.Readers.Odt.ContentReader
|
||||
- Text.Pandoc.Readers.Odt.Namespaces
|
||||
|
|
|
@ -13,6 +13,7 @@ module Text.Pandoc.Lua.Module.MediaBag
|
|||
( pushModule
|
||||
) where
|
||||
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Monad (zipWithM_)
|
||||
import Foreign.Lua (Lua, NumResults, Optional)
|
||||
import Text.Pandoc.Class.CommonState (CommonState (..))
|
||||
|
@ -36,10 +37,10 @@ pushModule = do
|
|||
liftPandocLua Lua.newtable
|
||||
addFunction "delete" delete
|
||||
addFunction "empty" empty
|
||||
addFunction "insert" insertMediaFn
|
||||
addFunction "insert" insert
|
||||
addFunction "items" items
|
||||
addFunction "lookup" lookupMediaFn
|
||||
addFunction "list" mediaDirectoryFn
|
||||
addFunction "lookup" lookup
|
||||
addFunction "list" list
|
||||
addFunction "fetch" fetch
|
||||
return 1
|
||||
|
||||
|
@ -53,11 +54,11 @@ empty :: PandocLua NumResults
|
|||
empty = 0 <$ modifyCommonState (\st -> st { stMediaBag = mempty })
|
||||
|
||||
-- | Insert a new item into the media bag.
|
||||
insertMediaFn :: FilePath
|
||||
-> Optional MimeType
|
||||
-> BL.ByteString
|
||||
-> PandocLua NumResults
|
||||
insertMediaFn fp optionalMime contents = do
|
||||
insert :: FilePath
|
||||
-> Optional MimeType
|
||||
-> BL.ByteString
|
||||
-> PandocLua NumResults
|
||||
insert fp optionalMime contents = do
|
||||
mb <- getMediaBag
|
||||
setMediaBag $ MB.insertMedia fp (Lua.fromOptional optionalMime) contents mb
|
||||
return (Lua.NumResults 0)
|
||||
|
@ -66,9 +67,9 @@ insertMediaFn fp optionalMime contents = do
|
|||
items :: PandocLua NumResults
|
||||
items = getMediaBag >>= liftPandocLua . pushIterator
|
||||
|
||||
lookupMediaFn :: FilePath
|
||||
-> PandocLua NumResults
|
||||
lookupMediaFn fp = do
|
||||
lookup :: FilePath
|
||||
-> PandocLua NumResults
|
||||
lookup fp = do
|
||||
res <- MB.lookupMedia fp <$> getMediaBag
|
||||
liftPandocLua $ case res of
|
||||
Nothing -> 1 <$ Lua.pushnil
|
||||
|
@ -77,8 +78,8 @@ lookupMediaFn fp = do
|
|||
Lua.push contents
|
||||
return 2
|
||||
|
||||
mediaDirectoryFn :: PandocLua NumResults
|
||||
mediaDirectoryFn = do
|
||||
list :: PandocLua NumResults
|
||||
list = do
|
||||
dirContents <- MB.mediaDirectory <$> getMediaBag
|
||||
liftPandocLua $ do
|
||||
Lua.newtable
|
||||
|
|
|
@ -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 (..))
|
||||
|
@ -43,10 +44,10 @@ import Text.Pandoc.Error
|
|||
pushModule :: PandocLua NumResults
|
||||
pushModule = do
|
||||
loadDefaultModule "pandoc"
|
||||
addFunction "read" readDoc
|
||||
addFunction "pipe" pipeFn
|
||||
addFunction "walk_block" walkBlock
|
||||
addFunction "walk_inline" walkInline
|
||||
addFunction "read" read
|
||||
addFunction "pipe" pipe
|
||||
addFunction "walk_block" walk_block
|
||||
addFunction "walk_inline" walk_inline
|
||||
return 1
|
||||
|
||||
walkElement :: (Walkable (SingletonsList Inline) a,
|
||||
|
@ -54,14 +55,14 @@ walkElement :: (Walkable (SingletonsList Inline) a,
|
|||
=> a -> LuaFilter -> PandocLua a
|
||||
walkElement x f = liftPandocLua $ walkInlines f x >>= walkBlocks 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 +80,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
|
||||
|
|
Loading…
Reference in a new issue