2017-09-12 01:20:49 +02:00
|
|
|
{-# LANGUAGE CPP #-}
|
2017-06-20 21:11:01 +02:00
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
2017-06-29 17:07:30 +02:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
2017-09-12 01:20:49 +02:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
2017-03-20 15:17:03 +01:00
|
|
|
{-
|
|
|
|
Copyright © 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
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
|
|
|
|
-}
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.Lua
|
|
|
|
Copyright : Copyright © 2017 Albert Krewinkel
|
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
|
|
|
Stability : alpha
|
|
|
|
|
|
|
|
Pandoc lua utils.
|
|
|
|
-}
|
2017-08-13 14:55:33 +02:00
|
|
|
module Text.Pandoc.Lua (LuaException (..), pushPandocModule, runLuaFilter) where
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-08-22 22:02:30 +02:00
|
|
|
import Control.Monad (mplus, unless, when, (>=>))
|
2017-09-12 01:20:49 +02:00
|
|
|
import Control.Monad.Identity (Identity)
|
2017-06-03 12:28:52 +02:00
|
|
|
import Control.Monad.Trans (MonadIO (..))
|
2017-08-22 22:02:30 +02:00
|
|
|
import Data.Data (DataType, Data, toConstr, showConstr, dataTypeOf,
|
2017-08-23 09:43:49 +02:00
|
|
|
dataTypeConstrs, dataTypeName, tyconUQname)
|
2017-08-22 22:02:30 +02:00
|
|
|
import Data.Foldable (foldrM)
|
2017-09-29 00:11:52 +02:00
|
|
|
import Data.IORef (IORef, newIORef, readIORef)
|
2017-06-03 12:28:52 +02:00
|
|
|
import Data.Map (Map)
|
2017-06-29 17:07:30 +02:00
|
|
|
import Data.Maybe (isJust)
|
2017-08-13 14:55:33 +02:00
|
|
|
import Foreign.Lua (Lua, FromLuaStack (peek), LuaException (..), StackIndex,
|
2017-09-12 01:20:49 +02:00
|
|
|
Status (OK), ToLuaStack (push))
|
2017-09-29 00:11:52 +02:00
|
|
|
import Text.Pandoc.Class (PandocIO, getMediaBag, setMediaBag)
|
|
|
|
import Text.Pandoc.MediaBag (MediaBag)
|
2017-04-14 23:24:52 +02:00
|
|
|
import Text.Pandoc.Definition
|
2017-09-29 00:11:52 +02:00
|
|
|
import Text.Pandoc.Lua.PandocModule (pushPandocModule, pushMediaBagModule)
|
2017-09-12 01:20:49 +02:00
|
|
|
import Text.Pandoc.Walk (walkM)
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-04-14 10:43:44 +02:00
|
|
|
import qualified Data.Map as Map
|
2017-08-22 22:02:30 +02:00
|
|
|
import qualified Foreign.Lua as Lua
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-09-29 00:11:52 +02:00
|
|
|
runLuaFilter :: Maybe FilePath -> FilePath -> String
|
|
|
|
-> Pandoc -> PandocIO (Either LuaException Pandoc)
|
|
|
|
runLuaFilter datadir filterPath format pd = do
|
|
|
|
mediaBag <- getMediaBag
|
|
|
|
mediaBagRef <- liftIO (newIORef mediaBag)
|
|
|
|
res <- liftIO . Lua.runLuaEither $
|
|
|
|
runLuaFilter' datadir filterPath format mediaBagRef pd
|
|
|
|
newMediaBag <- liftIO (readIORef mediaBagRef)
|
|
|
|
setMediaBag newMediaBag
|
|
|
|
return res
|
|
|
|
|
|
|
|
runLuaFilter' :: Maybe FilePath -> FilePath -> String -> IORef MediaBag
|
|
|
|
-> Pandoc -> Lua Pandoc
|
|
|
|
runLuaFilter' datadir filterPath format mbRef pd = do
|
2017-08-22 22:02:30 +02:00
|
|
|
Lua.openlibs
|
2017-04-04 21:51:51 +02:00
|
|
|
-- store module in global "pandoc"
|
2017-08-13 12:37:10 +02:00
|
|
|
pushPandocModule datadir
|
2017-08-22 22:02:30 +02:00
|
|
|
Lua.setglobal "pandoc"
|
2017-09-29 00:11:52 +02:00
|
|
|
addMediaBagModule
|
|
|
|
registerFormat
|
2017-08-22 22:02:30 +02:00
|
|
|
top <- Lua.gettop
|
2017-09-12 01:20:49 +02:00
|
|
|
stat <- Lua.dofile filterPath
|
2017-08-13 12:37:10 +02:00
|
|
|
if stat /= OK
|
2017-03-20 15:17:03 +01:00
|
|
|
then do
|
2017-08-22 22:02:30 +02:00
|
|
|
luaErrMsg <- peek (-1) <* Lua.pop 1
|
|
|
|
Lua.throwLuaError luaErrMsg
|
2017-03-20 15:17:03 +01:00
|
|
|
else do
|
2017-08-22 22:02:30 +02:00
|
|
|
newtop <- Lua.gettop
|
2017-04-30 16:14:33 +02:00
|
|
|
-- Use the implicitly defined global filter if nothing was returned
|
2017-09-12 01:20:49 +02:00
|
|
|
when (newtop - top < 1) pushGlobalFilter
|
2017-08-13 12:37:10 +02:00
|
|
|
luaFilters <- peek (-1)
|
|
|
|
runAll luaFilters pd
|
2017-09-29 00:11:52 +02:00
|
|
|
where
|
|
|
|
addMediaBagModule = do
|
|
|
|
Lua.getglobal "pandoc"
|
|
|
|
push "mediabag"
|
|
|
|
pushMediaBagModule mbRef
|
|
|
|
Lua.rawset (-3)
|
|
|
|
registerFormat = do
|
|
|
|
push format
|
|
|
|
Lua.setglobal "FORMAT"
|
|
|
|
|
2017-08-13 12:37:10 +02:00
|
|
|
|
|
|
|
pushGlobalFilter :: Lua ()
|
|
|
|
pushGlobalFilter = do
|
2017-08-22 22:02:30 +02:00
|
|
|
Lua.newtable
|
|
|
|
Lua.getglobal' "pandoc.global_filter"
|
|
|
|
Lua.call 0 1
|
|
|
|
Lua.rawseti (-2) 1
|
2017-08-13 12:37:10 +02:00
|
|
|
|
|
|
|
runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
|
2017-06-20 19:20:50 +02:00
|
|
|
runAll = foldr ((>=>) . walkMWithLuaFilter) return
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-08-13 12:37:10 +02:00
|
|
|
walkMWithLuaFilter :: LuaFilter -> Pandoc -> Lua Pandoc
|
2017-09-12 01:20:49 +02:00
|
|
|
walkMWithLuaFilter (LuaFilter fnMap) =
|
|
|
|
walkInlines >=> walkBlocks >=> walkMeta >=> walkPandoc
|
|
|
|
where
|
|
|
|
walkInlines :: Pandoc -> Lua Pandoc
|
|
|
|
walkInlines =
|
|
|
|
if hasOneOf inlineFilterNames
|
|
|
|
then walkM (mconcatMapM (tryFilter fnMap :: Inline -> Lua [Inline]))
|
|
|
|
else return
|
|
|
|
|
|
|
|
walkBlocks :: Pandoc -> Lua Pandoc
|
|
|
|
walkBlocks =
|
|
|
|
if hasOneOf blockFilterNames
|
|
|
|
then walkM (mconcatMapM (tryFilter fnMap :: Block -> Lua [Block]))
|
|
|
|
else return
|
|
|
|
|
|
|
|
walkMeta :: Pandoc -> Lua Pandoc
|
|
|
|
walkMeta =
|
|
|
|
case Map.lookup "Meta" fnMap of
|
|
|
|
Just fn -> walkM (\(Pandoc meta blocks) -> do
|
|
|
|
meta' <- runFilterFunction fn meta *> singleElement meta
|
|
|
|
return $ Pandoc meta' blocks)
|
|
|
|
Nothing -> return
|
|
|
|
|
|
|
|
walkPandoc :: Pandoc -> Lua Pandoc
|
|
|
|
walkPandoc =
|
|
|
|
case foldl mplus Nothing (map (`Map.lookup` fnMap) pandocFilterNames) of
|
|
|
|
Just fn -> \x -> runFilterFunction fn x *> singleElement x
|
|
|
|
Nothing -> return
|
|
|
|
|
|
|
|
mconcatMapM f = fmap mconcat . mapM f
|
2017-08-13 12:37:10 +02:00
|
|
|
hasOneOf = any (\k -> isJust (Map.lookup k fnMap))
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-08-22 22:02:30 +02:00
|
|
|
constructorsFor :: DataType -> [String]
|
|
|
|
constructorsFor x = map show (dataTypeConstrs x)
|
|
|
|
|
|
|
|
inlineFilterNames :: [String]
|
2017-08-22 23:12:39 +02:00
|
|
|
inlineFilterNames = "Inline" : constructorsFor (dataTypeOf (Str []))
|
2017-08-22 22:02:30 +02:00
|
|
|
|
|
|
|
blockFilterNames :: [String]
|
2017-08-22 23:12:39 +02:00
|
|
|
blockFilterNames = "Block" : constructorsFor (dataTypeOf (Para []))
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-08-22 22:02:30 +02:00
|
|
|
metaFilterName :: String
|
|
|
|
metaFilterName = "Meta"
|
|
|
|
|
|
|
|
pandocFilterNames :: [String]
|
|
|
|
pandocFilterNames = ["Pandoc", "Doc"]
|
|
|
|
|
|
|
|
type FunctionMap = Map String LuaFilterFunction
|
|
|
|
newtype LuaFilter = LuaFilter FunctionMap
|
2017-04-18 19:05:52 +02:00
|
|
|
newtype LuaFilterFunction = LuaFilterFunction { functionIndex :: Int }
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-08-13 12:37:10 +02:00
|
|
|
-- | Try running a filter for the given element
|
2017-09-12 01:20:49 +02:00
|
|
|
tryFilter :: (Data a, FromLuaStack a, ToLuaStack a)
|
|
|
|
=> FunctionMap -> a -> Lua [a]
|
2017-08-13 12:37:10 +02:00
|
|
|
tryFilter fnMap x =
|
2017-08-22 23:12:39 +02:00
|
|
|
let filterFnName = showConstr (toConstr x)
|
2017-08-23 09:43:49 +02:00
|
|
|
catchAllName = tyconUQname $ dataTypeName (dataTypeOf x)
|
2017-08-22 23:12:39 +02:00
|
|
|
in
|
|
|
|
case Map.lookup filterFnName fnMap `mplus` Map.lookup catchAllName fnMap of
|
2017-09-12 01:20:49 +02:00
|
|
|
Just fn -> runFilterFunction fn x *> elementOrList x
|
|
|
|
Nothing -> return [x]
|
2017-06-29 15:47:27 +02:00
|
|
|
|
2017-08-13 12:37:10 +02:00
|
|
|
instance FromLuaStack LuaFilter where
|
2017-08-22 22:02:30 +02:00
|
|
|
peek idx =
|
|
|
|
let constrs = metaFilterName : pandocFilterNames
|
|
|
|
++ blockFilterNames
|
|
|
|
++ inlineFilterNames
|
|
|
|
fn c acc = do
|
|
|
|
Lua.getfield idx c
|
|
|
|
filterFn <- Lua.tryLua (peek (-1))
|
|
|
|
Lua.pop 1
|
|
|
|
return $ case filterFn of
|
|
|
|
Left _ -> acc
|
|
|
|
Right f -> (c, f) : acc
|
|
|
|
in LuaFilter . Map.fromList <$> foldrM fn [] constrs
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-06-20 20:51:10 +02:00
|
|
|
-- | Push a value to the stack via a lua filter function. The filter function is
|
2017-06-27 17:11:42 +02:00
|
|
|
-- called with given element as argument and is expected to return an element.
|
|
|
|
-- Alternatively, the function can return nothing or nil, in which case the
|
|
|
|
-- element is left unchanged.
|
2017-09-12 01:20:49 +02:00
|
|
|
runFilterFunction :: ToLuaStack a => LuaFilterFunction -> a -> Lua ()
|
2017-08-13 12:37:10 +02:00
|
|
|
runFilterFunction lf x = do
|
|
|
|
pushFilterFunction lf
|
|
|
|
push x
|
2017-08-22 22:02:30 +02:00
|
|
|
z <- Lua.pcall 1 1 Nothing
|
2017-09-12 01:20:49 +02:00
|
|
|
when (z /= OK) $ do
|
|
|
|
msg <- Lua.peek (-1) <* Lua.pop 1
|
|
|
|
let prefix = "Error while running filter function: "
|
|
|
|
Lua.throwLuaError $ prefix ++ msg
|
|
|
|
|
|
|
|
elementOrList :: FromLuaStack a => a -> Lua [a]
|
|
|
|
elementOrList x = do
|
|
|
|
let topOfStack = Lua.StackIndex (-1)
|
|
|
|
elementUnchanged <- Lua.isnil topOfStack
|
|
|
|
if elementUnchanged
|
|
|
|
then [x] <$ Lua.pop 1
|
|
|
|
else do
|
|
|
|
mbres <- Lua.peekEither topOfStack
|
|
|
|
case mbres of
|
|
|
|
Right res -> [res] <$ Lua.pop 1
|
|
|
|
Left _ -> Lua.toList topOfStack <* Lua.pop 1
|
|
|
|
|
|
|
|
singleElement :: FromLuaStack a => a -> Lua a
|
|
|
|
singleElement x = do
|
|
|
|
elementUnchanged <- Lua.isnil (-1)
|
|
|
|
if elementUnchanged
|
|
|
|
then x <$ Lua.pop 1
|
2017-06-27 17:55:47 +02:00
|
|
|
else do
|
2017-09-12 01:20:49 +02:00
|
|
|
mbres <- Lua.peekEither (-1)
|
|
|
|
case mbres of
|
|
|
|
Right res -> res <$ Lua.pop 1
|
|
|
|
Left err -> do
|
|
|
|
Lua.pop 1
|
|
|
|
Lua.throwLuaError $
|
|
|
|
"Error while trying to get a filter's return " ++
|
|
|
|
"value from lua stack.\n" ++ err
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-04-04 21:51:51 +02:00
|
|
|
-- | Push the filter function to the top of the stack.
|
2017-08-13 12:37:10 +02:00
|
|
|
pushFilterFunction :: LuaFilterFunction -> Lua ()
|
|
|
|
pushFilterFunction lf =
|
2017-04-04 21:51:51 +02:00
|
|
|
-- The function is stored in a lua registry table, retrieve it from there.
|
2017-08-22 22:02:30 +02:00
|
|
|
Lua.rawgeti Lua.registryindex (functionIndex lf)
|
2017-08-13 12:37:10 +02:00
|
|
|
|
|
|
|
registerFilterFunction :: StackIndex -> Lua LuaFilterFunction
|
|
|
|
registerFilterFunction idx = do
|
2017-08-22 22:02:30 +02:00
|
|
|
isFn <- Lua.isfunction idx
|
|
|
|
unless isFn . Lua.throwLuaError $ "Not a function at index " ++ show idx
|
|
|
|
Lua.pushvalue idx
|
|
|
|
refIdx <- Lua.ref Lua.registryindex
|
2017-06-20 20:51:10 +02:00
|
|
|
return $ LuaFilterFunction refIdx
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-09-12 01:20:49 +02:00
|
|
|
instance (FromLuaStack a) => FromLuaStack (Identity a) where
|
|
|
|
peek = fmap return . peek
|
|
|
|
|
2017-08-13 12:37:10 +02:00
|
|
|
instance ToLuaStack LuaFilterFunction where
|
2017-06-20 19:20:50 +02:00
|
|
|
push = pushFilterFunction
|
2017-08-13 12:37:10 +02:00
|
|
|
|
|
|
|
instance FromLuaStack LuaFilterFunction where
|
|
|
|
peek = registerFilterFunction
|