aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Module')
-rw-r--r--src/Text/Pandoc/Lua/Module/MediaBag.hs2
-rw-r--r--src/Text/Pandoc/Lua/Module/Pandoc.hs35
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs34
3 files changed, 41 insertions, 30 deletions
diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs
index f48fe56c5..150c06cc8 100644
--- a/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -87,7 +87,7 @@ mediaDirectoryFn mbRef = do
zipWithM_ addEntry [1..] dirContents
return 1
where
- addEntry :: Int -> (FilePath, MimeType, Int) -> Lua ()
+ addEntry :: Lua.Integer -> (FilePath, MimeType, Int) -> Lua ()
addEntry idx (fp, mimeType, contentLength) = do
Lua.newtable
Lua.push "path" *> Lua.push fp *> Lua.rawset (-3)
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index 8cb630d7b..769b04b9e 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-
Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -17,6 +16,7 @@ along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Text.Pandoc.Lua.Module.Pandoc
Copyright : Copyright © 2017-2018 Albert Krewinkel
@@ -36,13 +36,12 @@ import Control.Monad (when)
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
import Data.Text (pack)
-import Foreign.Lua (ToLuaStack, FromLuaStack, Lua, NumResults, Optional, liftIO)
+import Foreign.Lua (Lua, NumResults, Optional, Peekable, Pushable)
import System.Exit (ExitCode (..))
import Text.Pandoc.Class (runIO)
import Text.Pandoc.Definition (Block, Inline)
import Text.Pandoc.Lua.Filter (walkInlines, walkBlocks, LuaFilter)
import Text.Pandoc.Lua.StackInstances ()
-import Text.Pandoc.Lua.Util (addFunction, addValue, loadScriptFromDataDir)
import Text.Pandoc.Walk (Walkable)
import Text.Pandoc.Options (ReaderOptions (readerExtensions))
import Text.Pandoc.Process (pipeProcess)
@@ -51,19 +50,20 @@ import Text.Pandoc.Readers (Reader (..), getReader)
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Foreign.Lua as Lua
+import qualified Text.Pandoc.Lua.Util as LuaUtil
-- | Push the "pandoc" on the lua stack. Requires the `list` module to be
-- loaded.
pushModule :: Maybe FilePath -> Lua NumResults
pushModule datadir = do
- loadScriptFromDataDir datadir "pandoc.lua"
- addFunction "read" readDoc
- addFunction "pipe" pipeFn
- addFunction "walk_block" walkBlock
- addFunction "walk_inline" walkInline
+ LuaUtil.loadScriptFromDataDir datadir "pandoc.lua"
+ LuaUtil.addFunction "read" readDoc
+ LuaUtil.addFunction "pipe" pipeFn
+ LuaUtil.addFunction "walk_block" walkBlock
+ LuaUtil.addFunction "walk_inline" walkInline
return 1
-walkElement :: (ToLuaStack a, Walkable [Inline] a, Walkable [Block] a)
+walkElement :: (Pushable a, Walkable [Inline] a, Walkable [Block] a)
=> a -> LuaFilter -> Lua a
walkElement x f = walkInlines f x >>= walkBlocks f
@@ -81,7 +81,8 @@ readDoc content formatSpecOrNil = do
Right (reader, es) ->
case reader of
TextReader r -> do
- res <- liftIO $ runIO $ r def{ readerExtensions = es } (pack content)
+ res <- Lua.liftIO . runIO $
+ r def{ readerExtensions = es } (pack content)
case res of
Right pd -> (1 :: NumResults) <$ Lua.push pd -- success, push Pandoc
Left s -> Lua.raiseError (show s) -- error while reading
@@ -93,7 +94,7 @@ pipeFn :: String
-> BL.ByteString
-> Lua NumResults
pipeFn command args input = do
- (ec, output) <- liftIO $ pipeProcess Nothing command args input
+ (ec, output) <- Lua.liftIO $ pipeProcess Nothing command args input
case ec of
ExitSuccess -> 1 <$ Lua.push output
ExitFailure n -> Lua.raiseError (PipeError command n output)
@@ -104,26 +105,26 @@ data PipeError = PipeError
, pipeErrorOutput :: BL.ByteString
}
-instance FromLuaStack PipeError where
+instance Peekable PipeError where
peek idx =
PipeError
<$> (Lua.getfield idx "command" *> Lua.peek (-1) <* Lua.pop 1)
<*> (Lua.getfield idx "error_code" *> Lua.peek (-1) <* Lua.pop 1)
<*> (Lua.getfield idx "output" *> Lua.peek (-1) <* Lua.pop 1)
-instance ToLuaStack PipeError where
+instance Pushable PipeError where
push pipeErr = do
Lua.newtable
- addValue "command" (pipeErrorCommand pipeErr)
- addValue "error_code" (pipeErrorCode pipeErr)
- addValue "output" (pipeErrorOutput pipeErr)
+ LuaUtil.addField "command" (pipeErrorCommand pipeErr)
+ LuaUtil.addField "error_code" (pipeErrorCode pipeErr)
+ LuaUtil.addField "output" (pipeErrorOutput pipeErr)
pushPipeErrorMetaTable
Lua.setmetatable (-2)
where
pushPipeErrorMetaTable :: Lua ()
pushPipeErrorMetaTable = do
v <- Lua.newmetatable "pandoc pipe error"
- when v $ addFunction "__tostring" pipeErrorMessage
+ when v $ LuaUtil.addFunction "__tostring" pipeErrorMessage
pipeErrorMessage :: PipeError -> Lua BL.ByteString
pipeErrorMessage (PipeError cmd errorCode output) = return $ mconcat
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 7fa4616be..030d6af95 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-
Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -16,6 +15,7 @@ You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
+{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Text.Pandoc.Lua.Module.Utils
Copyright : Copyright © 2017-2018 Albert Krewinkel
@@ -33,15 +33,16 @@ module Text.Pandoc.Lua.Module.Utils
import Prelude
import Control.Applicative ((<|>))
import Data.Default (def)
-import Foreign.Lua (FromLuaStack, Lua, LuaInteger, NumResults)
+import Foreign.Lua (Peekable, Lua, NumResults)
import Text.Pandoc.Class (runIO, setUserDataDir)
import Text.Pandoc.Definition (Pandoc, Meta, MetaValue, Block, Inline)
import Text.Pandoc.Lua.StackInstances ()
-import Text.Pandoc.Lua.Util (addFunction, popValue)
+import Text.Pandoc.Lua.Util (addFunction)
import qualified Data.Digest.Pure.SHA as SHA
import qualified Data.ByteString.Lazy as BSL
import qualified Foreign.Lua as Lua
+import qualified Text.Pandoc.Builder as B
import qualified Text.Pandoc.Filter.JSON as JSONFilter
import qualified Text.Pandoc.Shared as Shared
@@ -49,6 +50,7 @@ import qualified Text.Pandoc.Shared as Shared
pushModule :: Maybe FilePath -> Lua NumResults
pushModule mbDatadir = do
Lua.newtable
+ addFunction "blocks_to_inlines" blocksToInlines
addFunction "hierarchicalize" hierarchicalize
addFunction "normalize_date" normalizeDate
addFunction "run_json_filter" (runJSONFilter mbDatadir)
@@ -57,6 +59,14 @@ pushModule mbDatadir = do
addFunction "to_roman_numeral" toRomanNumeral
return 1
+-- | Squashes a list of blocks into inlines.
+blocksToInlines :: [Block] -> Lua.Optional [Inline] -> Lua [Inline]
+blocksToInlines blks optSep = do
+ let sep = case Lua.fromOptional optSep of
+ Just x -> B.fromList x
+ Nothing -> Shared.defaultBlocksSeparator
+ return $ B.toList (Shared.blocksToInlinesWithSep sep blks)
+
-- | Convert list of Pandoc blocks into (hierarchical) list of Elements.
hierarchicalize :: [Block] -> Lua [Shared.Element]
hierarchicalize = return . Shared.hierarchicalize
@@ -79,7 +89,7 @@ runJSONFilter mbDatadir doc filterFile optArgs = do
Just x -> return x
Nothing -> do
Lua.getglobal "FORMAT"
- (:[]) <$> popValue
+ (:[]) <$> Lua.popValue
filterRes <- Lua.liftIO . runIO $ do
setUserDataDir mbDatadir
JSONFilter.apply def args filterFile doc
@@ -111,18 +121,18 @@ data AstElement
| MetaValueElement MetaValue
deriving (Show)
-instance FromLuaStack AstElement where
+instance Peekable AstElement where
peek idx = do
- res <- Lua.tryLua $ (PandocElement <$> Lua.peek idx)
- <|> (InlineElement <$> Lua.peek idx)
- <|> (BlockElement <$> Lua.peek idx)
- <|> (MetaElement <$> Lua.peek idx)
- <|> (MetaValueElement <$> Lua.peek idx)
+ res <- Lua.try $ (PandocElement <$> Lua.peek idx)
+ <|> (InlineElement <$> Lua.peek idx)
+ <|> (BlockElement <$> Lua.peek idx)
+ <|> (MetaElement <$> Lua.peek idx)
+ <|> (MetaValueElement <$> Lua.peek idx)
case res of
Right x -> return x
- Left _ -> Lua.throwLuaError
+ Left _ -> Lua.throwException
"Expected an AST element, but could not parse value as such."
-- | Convert a number < 4000 to uppercase roman numeral.
-toRomanNumeral :: LuaInteger -> Lua String
+toRomanNumeral :: Lua.Integer -> Lua String
toRomanNumeral = return . Shared.toRomanNumeral . fromIntegral