2017-06-20 21:11:01 +02:00
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
|
|
{-# LANGUAGE DeriveDataTypeable #-}
|
2017-06-29 17:07:30 +02:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
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-06-29 17:07:30 +02:00
|
|
|
import Control.Monad (unless, when, (>=>), mplus)
|
2017-06-03 12:28:52 +02:00
|
|
|
import Control.Monad.Trans (MonadIO (..))
|
2017-06-29 17:07:30 +02:00
|
|
|
import Data.Data (toConstr, showConstr, dataTypeOf, dataTypeConstrs, Data)
|
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,
|
|
|
|
Status(OK), ToLuaStack (push), call, isnil, dofile,
|
|
|
|
getglobal', gettop, isfunction, newtable, openlibs, pcall,
|
|
|
|
peekEither, pop, pushvalue, rawgeti, rawseti, ref,
|
|
|
|
registryindex, runLua, setglobal, throwLuaError)
|
2017-04-14 23:24:52 +02:00
|
|
|
import Text.Pandoc.Definition
|
2017-06-03 12:28:52 +02:00
|
|
|
import Text.Pandoc.Lua.PandocModule (pushPandocModule)
|
2017-08-13 14:55:33 +02:00
|
|
|
import Text.Pandoc.Walk (Walkable (walkM))
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-04-14 10:43:44 +02:00
|
|
|
import qualified Data.Map as Map
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
|
|
runLuaFilter :: (MonadIO m)
|
2017-06-29 17:13:19 +02:00
|
|
|
=> Maybe FilePath -> FilePath -> [String] -> Pandoc -> m Pandoc
|
2017-08-13 12:37:10 +02:00
|
|
|
runLuaFilter datadir filterPath args pd = liftIO . runLua $ do
|
|
|
|
openlibs
|
2017-04-04 21:51:51 +02:00
|
|
|
-- store module in global "pandoc"
|
2017-08-13 12:37:10 +02:00
|
|
|
pushPandocModule datadir
|
|
|
|
setglobal "pandoc"
|
|
|
|
top <- gettop
|
|
|
|
stat<- dofile filterPath
|
|
|
|
if stat /= OK
|
2017-03-20 15:17:03 +01:00
|
|
|
then do
|
2017-08-13 12:37:10 +02:00
|
|
|
luaErrMsg <- peek (-1) <* pop 1
|
|
|
|
throwLuaError luaErrMsg
|
2017-03-20 15:17:03 +01:00
|
|
|
else do
|
2017-08-13 12:37:10 +02:00
|
|
|
newtop <- gettop
|
2017-04-30 16:14:33 +02:00
|
|
|
-- Use the implicitly defined global filter if nothing was returned
|
2017-08-13 12:37:10 +02:00
|
|
|
when (newtop - top < 1) $ pushGlobalFilter
|
|
|
|
luaFilters <- peek (-1)
|
|
|
|
push args
|
|
|
|
setglobal "PandocParameters"
|
|
|
|
runAll luaFilters pd
|
|
|
|
|
|
|
|
pushGlobalFilter :: Lua ()
|
|
|
|
pushGlobalFilter = do
|
|
|
|
newtable
|
|
|
|
getglobal' "pandoc.global_filter"
|
|
|
|
call 0 1
|
|
|
|
rawseti (-2) 1
|
|
|
|
|
|
|
|
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-08-13 14:55:33 +02:00
|
|
|
walkMWithLuaFilter (LuaFilter fnMap) = walkLua
|
2017-08-13 12:37:10 +02:00
|
|
|
where
|
2017-08-13 14:55:33 +02:00
|
|
|
walkLua :: Pandoc -> Lua Pandoc
|
|
|
|
walkLua =
|
2017-08-13 12:37:10 +02:00
|
|
|
(if hasOneOf (constructorsFor (dataTypeOf (Str [])))
|
2017-08-13 14:55:33 +02:00
|
|
|
then walkM (tryFilter fnMap :: Inline -> Lua Inline)
|
2017-08-13 12:37:10 +02:00
|
|
|
else return)
|
|
|
|
>=>
|
|
|
|
(if hasOneOf (constructorsFor (dataTypeOf (Para [])))
|
2017-08-13 14:55:33 +02:00
|
|
|
then walkM (tryFilter fnMap :: Block -> Lua Block)
|
2017-08-13 12:37:10 +02:00
|
|
|
else return)
|
|
|
|
>=>
|
|
|
|
(case Map.lookup "Meta" fnMap of
|
2017-08-13 14:55:33 +02:00
|
|
|
Just fn -> walkM (\(Pandoc meta blocks) -> do
|
|
|
|
meta' <- runFilterFunction fn meta
|
|
|
|
return $ Pandoc meta' blocks)
|
2017-08-13 12:37:10 +02:00
|
|
|
Nothing -> return)
|
|
|
|
>=>
|
|
|
|
(case Map.lookup "Pandoc" fnMap `mplus` Map.lookup "Doc" fnMap of
|
2017-08-13 14:55:33 +02:00
|
|
|
Just fn -> runFilterFunction fn :: Pandoc -> Lua Pandoc
|
2017-08-13 12:37:10 +02:00
|
|
|
Nothing -> return)
|
|
|
|
hasOneOf = any (\k -> isJust (Map.lookup k fnMap))
|
|
|
|
constructorsFor x = map show (dataTypeConstrs x)
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-04-18 19:05:52 +02:00
|
|
|
type FunctionMap = Map String LuaFilterFunction
|
2017-08-13 12:37:10 +02:00
|
|
|
data LuaFilter = LuaFilter FunctionMap
|
2017-03-20 15:17:03 +01:00
|
|
|
|
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
|
|
|
|
tryFilter :: (Data a, FromLuaStack a, ToLuaStack a) => FunctionMap -> a -> Lua a
|
|
|
|
tryFilter fnMap x =
|
2017-06-29 17:07:30 +02:00
|
|
|
let filterFnName = showConstr (toConstr x) in
|
2017-06-29 15:47:27 +02:00
|
|
|
case Map.lookup filterFnName fnMap of
|
|
|
|
Nothing -> return x
|
2017-08-13 12:37:10 +02:00
|
|
|
Just fn -> runFilterFunction fn x
|
2017-06-29 15:47:27 +02:00
|
|
|
|
2017-08-13 12:37:10 +02:00
|
|
|
instance FromLuaStack LuaFilter where
|
|
|
|
peek idx = LuaFilter <$> peek idx
|
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-08-13 12:37:10 +02:00
|
|
|
runFilterFunction :: (FromLuaStack a, ToLuaStack a)
|
|
|
|
=> LuaFilterFunction -> a -> Lua a
|
|
|
|
runFilterFunction lf x = do
|
|
|
|
pushFilterFunction lf
|
|
|
|
push x
|
|
|
|
z <- pcall 1 1 Nothing
|
|
|
|
if z /= OK
|
2017-06-27 17:55:47 +02:00
|
|
|
then do
|
2017-08-13 12:37:10 +02:00
|
|
|
msg <- peek (-1)
|
2017-06-27 17:55:47 +02:00
|
|
|
let prefix = "Error while running filter function: "
|
2017-08-13 12:37:10 +02:00
|
|
|
throwLuaError $ prefix ++ msg
|
2017-06-27 17:55:47 +02:00
|
|
|
else do
|
2017-08-13 14:55:33 +02:00
|
|
|
noExplicitFilter <- isnil (-1)
|
|
|
|
if noExplicitFilter
|
|
|
|
then pop 1 *> return x
|
|
|
|
else do
|
2017-08-13 12:37:10 +02:00
|
|
|
mbres <- peekEither (-1)
|
2017-06-27 17:55:47 +02:00
|
|
|
case mbres of
|
2017-08-13 12:37:10 +02:00
|
|
|
Left err -> throwLuaError
|
|
|
|
("Error while trying to get a filter's return "
|
|
|
|
++ "value from lua stack.\n" ++ err)
|
|
|
|
Right res -> res <$ pop 1
|
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-13 12:37:10 +02:00
|
|
|
rawgeti registryindex (functionIndex lf)
|
|
|
|
|
|
|
|
registerFilterFunction :: StackIndex -> Lua LuaFilterFunction
|
|
|
|
registerFilterFunction idx = do
|
|
|
|
isFn <- isfunction idx
|
|
|
|
unless isFn . throwLuaError $ "Not a function at index " ++ show idx
|
|
|
|
pushvalue idx
|
|
|
|
refIdx <- ref registryindex
|
2017-06-20 20:51:10 +02:00
|
|
|
return $ LuaFilterFunction refIdx
|
2017-03-20 15:17:03 +01:00
|
|
|
|
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
|