2017-06-20 21:11:01 +02:00
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
|
|
{-# LANGUAGE DeriveDataTypeable #-}
|
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-06-20 16:09:33 +02:00
|
|
|
module Text.Pandoc.Lua ( LuaException(..),
|
|
|
|
runLuaFilter,
|
|
|
|
pushPandocModule ) where
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-06-20 16:09:33 +02:00
|
|
|
import Control.Exception
|
2017-06-03 12:28:52 +02:00
|
|
|
import Control.Monad (unless, when, (>=>))
|
|
|
|
import Control.Monad.Trans (MonadIO (..))
|
|
|
|
import Data.Map (Map)
|
2017-06-20 16:09:33 +02:00
|
|
|
import Data.Typeable (Typeable)
|
2017-06-03 12:28:52 +02:00
|
|
|
import Scripting.Lua (LuaState, StackValue (..))
|
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-04-02 17:21:22 +02:00
|
|
|
import Text.Pandoc.Lua.StackInstances ()
|
2017-03-20 15:17:03 +01:00
|
|
|
import Text.Pandoc.Walk
|
|
|
|
|
2017-04-14 10:43:44 +02:00
|
|
|
import qualified Data.Map as Map
|
2017-03-20 15:17:03 +01:00
|
|
|
import qualified Scripting.Lua as Lua
|
|
|
|
|
2017-06-20 19:20:50 +02:00
|
|
|
newtype LuaException = LuaException String
|
2017-06-20 16:09:33 +02:00
|
|
|
deriving (Show, Typeable)
|
|
|
|
|
|
|
|
instance Exception LuaException
|
|
|
|
|
2017-03-20 15:17:03 +01:00
|
|
|
runLuaFilter :: (MonadIO m)
|
|
|
|
=> FilePath -> [String] -> Pandoc -> m Pandoc
|
|
|
|
runLuaFilter filterPath args pd = liftIO $ do
|
2017-04-14 10:43:44 +02:00
|
|
|
lua <- Lua.newstate
|
2017-03-20 15:17:03 +01:00
|
|
|
Lua.openlibs lua
|
2017-04-04 21:51:51 +02:00
|
|
|
-- store module in global "pandoc"
|
2017-03-20 15:17:03 +01:00
|
|
|
pushPandocModule lua
|
|
|
|
Lua.setglobal lua "pandoc"
|
2017-04-30 16:14:33 +02:00
|
|
|
top <- Lua.gettop lua
|
2017-03-20 15:17:03 +01:00
|
|
|
status <- Lua.loadfile lua filterPath
|
2017-06-20 19:20:50 +02:00
|
|
|
if status /= 0
|
2017-03-20 15:17:03 +01:00
|
|
|
then do
|
2017-04-14 10:43:44 +02:00
|
|
|
Just luaErrMsg <- Lua.peek lua 1
|
2017-06-20 16:09:33 +02:00
|
|
|
throwIO (LuaException luaErrMsg)
|
2017-03-20 15:17:03 +01:00
|
|
|
else do
|
2017-04-30 16:14:33 +02:00
|
|
|
Lua.call lua 0 Lua.multret
|
|
|
|
newtop <- Lua.gettop lua
|
|
|
|
-- Use the implicitly defined global filter if nothing was returned
|
|
|
|
when (newtop - top < 1) $ pushGlobalFilter lua
|
2017-03-20 15:17:03 +01:00
|
|
|
Just luaFilters <- Lua.peek lua (-1)
|
2017-04-14 10:43:44 +02:00
|
|
|
Lua.push lua args
|
2017-03-20 15:17:03 +01:00
|
|
|
Lua.setglobal lua "PandocParameters"
|
2017-04-14 18:26:42 +02:00
|
|
|
doc <- runAll luaFilters pd
|
2017-03-20 15:17:03 +01:00
|
|
|
Lua.close lua
|
|
|
|
return doc
|
|
|
|
|
2017-04-30 16:14:33 +02:00
|
|
|
pushGlobalFilter :: LuaState -> IO ()
|
|
|
|
pushGlobalFilter lua =
|
|
|
|
Lua.newtable lua
|
|
|
|
*> Lua.getglobal2 lua "pandoc.global_filter"
|
|
|
|
*> Lua.call lua 0 1
|
|
|
|
*> Lua.rawseti lua (-2) 1
|
|
|
|
|
2017-03-20 15:17:03 +01:00
|
|
|
runAll :: [LuaFilter] -> Pandoc -> IO Pandoc
|
2017-06-20 19:20:50 +02:00
|
|
|
runAll = foldr ((>=>) . walkMWithLuaFilter) return
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
|
|
walkMWithLuaFilter :: LuaFilter -> Pandoc -> IO Pandoc
|
2017-04-18 19:05:52 +02:00
|
|
|
walkMWithLuaFilter (LuaFilter lua fnMap) =
|
|
|
|
walkM (execInlineLuaFilter lua fnMap) >=>
|
2017-04-16 21:06:50 +02:00
|
|
|
walkM (execBlockLuaFilter lua fnMap) >=>
|
|
|
|
walkM (execMetaLuaFilter lua fnMap) >=>
|
2017-04-18 19:05:52 +02:00
|
|
|
walkM (execDocLuaFilter lua fnMap)
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-04-18 19:05:52 +02:00
|
|
|
type FunctionMap = Map String LuaFilterFunction
|
|
|
|
data LuaFilter = LuaFilter LuaState 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
|
|
|
|
|
|
|
execDocLuaFilter :: LuaState
|
2017-04-18 19:05:52 +02:00
|
|
|
-> FunctionMap
|
2017-03-20 15:17:03 +01:00
|
|
|
-> Pandoc -> IO Pandoc
|
|
|
|
execDocLuaFilter lua fnMap x = do
|
|
|
|
let docFnName = "Doc"
|
2017-04-14 10:43:44 +02:00
|
|
|
case Map.lookup docFnName fnMap of
|
2017-03-20 15:17:03 +01:00
|
|
|
Nothing -> return x
|
2017-06-20 20:51:10 +02:00
|
|
|
Just fn -> runFilterFunction lua fn x
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-04-16 21:06:50 +02:00
|
|
|
execMetaLuaFilter :: LuaState
|
|
|
|
-> FunctionMap
|
|
|
|
-> Pandoc -> IO Pandoc
|
|
|
|
execMetaLuaFilter lua fnMap pd@(Pandoc meta blks) = do
|
|
|
|
let metaFnName = "Meta"
|
|
|
|
case Map.lookup metaFnName fnMap of
|
|
|
|
Nothing -> return pd
|
|
|
|
Just fn -> do
|
2017-06-20 20:51:10 +02:00
|
|
|
meta' <- runFilterFunction lua fn meta
|
2017-04-16 21:06:50 +02:00
|
|
|
return $ Pandoc meta' blks
|
|
|
|
|
2017-03-20 15:17:03 +01:00
|
|
|
execBlockLuaFilter :: LuaState
|
2017-04-18 19:05:52 +02:00
|
|
|
-> FunctionMap
|
2017-03-20 15:17:03 +01:00
|
|
|
-> Block -> IO Block
|
|
|
|
execBlockLuaFilter lua fnMap x = do
|
2017-04-15 21:40:48 +02:00
|
|
|
let tryFilter :: String -> IO Block
|
|
|
|
tryFilter filterFnName =
|
|
|
|
case Map.lookup filterFnName fnMap of
|
2017-04-14 11:21:58 +02:00
|
|
|
Nothing -> return x
|
2017-06-20 20:51:10 +02:00
|
|
|
Just fn -> runFilterFunction lua fn x
|
2017-03-20 15:17:03 +01:00
|
|
|
case x of
|
2017-06-20 19:20:50 +02:00
|
|
|
BlockQuote{} -> tryFilter "BlockQuote"
|
|
|
|
BulletList{} -> tryFilter "BulletList"
|
|
|
|
CodeBlock{} -> tryFilter "CodeBlock"
|
|
|
|
DefinitionList{} -> tryFilter "DefinitionList"
|
|
|
|
Div{} -> tryFilter "Div"
|
|
|
|
Header{} -> tryFilter "Header"
|
2017-04-15 21:40:48 +02:00
|
|
|
HorizontalRule -> tryFilter "HorizontalRule"
|
2017-06-20 19:20:50 +02:00
|
|
|
LineBlock{} -> tryFilter "LineBlock"
|
2017-04-15 21:40:48 +02:00
|
|
|
Null -> tryFilter "Null"
|
2017-06-20 19:20:50 +02:00
|
|
|
Para{} -> tryFilter "Para"
|
|
|
|
Plain{} -> tryFilter "Plain"
|
|
|
|
RawBlock{} -> tryFilter "RawBlock"
|
|
|
|
OrderedList{} -> tryFilter "OrderedList"
|
|
|
|
Table{} -> tryFilter "Table"
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
|
|
execInlineLuaFilter :: LuaState
|
2017-04-18 19:05:52 +02:00
|
|
|
-> FunctionMap
|
2017-03-20 15:17:03 +01:00
|
|
|
-> Inline -> IO Inline
|
|
|
|
execInlineLuaFilter lua fnMap x = do
|
2017-04-15 21:40:48 +02:00
|
|
|
let tryFilter :: String -> IO Inline
|
|
|
|
tryFilter filterFnName =
|
|
|
|
case Map.lookup filterFnName fnMap of
|
2017-04-12 20:48:44 +02:00
|
|
|
Nothing -> return x
|
2017-06-20 20:51:10 +02:00
|
|
|
Just fn -> runFilterFunction lua fn x
|
2017-04-15 21:40:48 +02:00
|
|
|
let tryFilterAlternatives :: [String] -> IO Inline
|
2017-04-14 23:24:52 +02:00
|
|
|
tryFilterAlternatives [] = return x
|
2017-04-15 21:40:48 +02:00
|
|
|
tryFilterAlternatives (fnName : alternatives) =
|
2017-04-14 23:24:52 +02:00
|
|
|
case Map.lookup fnName fnMap of
|
|
|
|
Nothing -> tryFilterAlternatives alternatives
|
2017-06-20 20:51:10 +02:00
|
|
|
Just fn -> runFilterFunction lua fn x
|
2017-03-20 15:17:03 +01:00
|
|
|
case x of
|
2017-06-20 19:20:50 +02:00
|
|
|
Cite{} -> tryFilter "Cite"
|
|
|
|
Code{} -> tryFilter "Code"
|
|
|
|
Emph{} -> tryFilter "Emph"
|
|
|
|
Image{} -> tryFilter "Image"
|
2017-04-15 21:40:48 +02:00
|
|
|
LineBreak -> tryFilter "LineBreak"
|
2017-06-20 19:20:50 +02:00
|
|
|
Link{} -> tryFilter "Link"
|
2017-04-15 21:40:48 +02:00
|
|
|
Math DisplayMath _ -> tryFilterAlternatives ["DisplayMath", "Math"]
|
|
|
|
Math InlineMath _ -> tryFilterAlternatives ["InlineMath", "Math"]
|
2017-06-20 19:20:50 +02:00
|
|
|
Note{} -> tryFilter "Note"
|
2017-04-15 21:40:48 +02:00
|
|
|
Quoted DoubleQuote _ -> tryFilterAlternatives ["DoubleQuoted", "Quoted"]
|
|
|
|
Quoted SingleQuote _ -> tryFilterAlternatives ["SingleQuoted", "Quoted"]
|
2017-06-20 19:20:50 +02:00
|
|
|
RawInline{} -> tryFilter "RawInline"
|
|
|
|
SmallCaps{} -> tryFilter "SmallCaps"
|
2017-04-15 21:40:48 +02:00
|
|
|
SoftBreak -> tryFilter "SoftBreak"
|
|
|
|
Space -> tryFilter "Space"
|
2017-06-20 19:20:50 +02:00
|
|
|
Span{} -> tryFilter "Span"
|
|
|
|
Str{} -> tryFilter "Str"
|
|
|
|
Strikeout{} -> tryFilter "Strikeout"
|
|
|
|
Strong{} -> tryFilter "Strong"
|
|
|
|
Subscript{} -> tryFilter "Subscript"
|
|
|
|
Superscript{} -> tryFilter "Superscript"
|
2017-03-20 15:17:03 +01:00
|
|
|
|
|
|
|
instance StackValue LuaFilter where
|
|
|
|
valuetype _ = Lua.TTABLE
|
|
|
|
push = undefined
|
2017-04-18 19:05:52 +02:00
|
|
|
peek lua idx = fmap (LuaFilter lua) <$> Lua.peek lua idx
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-04-12 20:48:44 +02:00
|
|
|
-- | Helper class for pushing a single value to the stack via a lua function.
|
|
|
|
-- See @pushViaCall@.
|
2017-04-18 19:05:52 +02:00
|
|
|
class PushViaFilterFunction a where
|
|
|
|
pushViaFilterFunction' :: LuaState -> LuaFilterFunction -> IO () -> Int -> a
|
2017-04-12 20:48:44 +02:00
|
|
|
|
2017-04-18 19:05:52 +02:00
|
|
|
instance StackValue a => PushViaFilterFunction (IO a) where
|
2017-04-12 20:48:44 +02:00
|
|
|
pushViaFilterFunction' lua lf pushArgs num = do
|
|
|
|
pushFilterFunction lua lf
|
|
|
|
pushArgs
|
|
|
|
Lua.call lua num 1
|
|
|
|
mbres <- Lua.peek lua (-1)
|
|
|
|
case mbres of
|
2017-06-20 16:09:33 +02:00
|
|
|
Nothing -> throwIO $ LuaException
|
|
|
|
("Error while trying to get a filter's return "
|
|
|
|
++ "value from lua stack.")
|
2017-04-12 20:48:44 +02:00
|
|
|
Just res -> res <$ Lua.pop lua 1
|
|
|
|
|
2017-04-18 19:05:52 +02:00
|
|
|
instance (StackValue a, PushViaFilterFunction b) =>
|
|
|
|
PushViaFilterFunction (a -> b) where
|
2017-04-12 20:48:44 +02:00
|
|
|
pushViaFilterFunction' lua lf pushArgs num x =
|
|
|
|
pushViaFilterFunction' lua lf (pushArgs *> push lua x) (num + 1)
|
|
|
|
|
2017-06-20 20:51:10 +02:00
|
|
|
-- | Push a value to the stack via a lua filter function. The filter function is
|
2017-04-12 20:48:44 +02:00
|
|
|
-- called with all arguments that are passed to this function and is expected to
|
|
|
|
-- return a single value.
|
2017-06-20 20:51:10 +02:00
|
|
|
runFilterFunction :: PushViaFilterFunction a
|
2017-04-18 19:05:52 +02:00
|
|
|
=> LuaState -> LuaFilterFunction -> a
|
2017-06-20 20:51:10 +02:00
|
|
|
runFilterFunction lua lf = pushViaFilterFunction' lua lf (return ()) 0
|
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-04-18 19:05:52 +02:00
|
|
|
pushFilterFunction :: Lua.LuaState -> LuaFilterFunction -> IO ()
|
2017-06-20 20:51:10 +02:00
|
|
|
pushFilterFunction lua lf =
|
2017-04-04 21:51:51 +02:00
|
|
|
-- The function is stored in a lua registry table, retrieve it from there.
|
2017-06-20 20:51:10 +02:00
|
|
|
Lua.rawgeti lua Lua.registryindex (functionIndex lf)
|
|
|
|
|
|
|
|
registerFilterFunction :: LuaState -> Int -> IO LuaFilterFunction
|
|
|
|
registerFilterFunction lua idx = do
|
|
|
|
isFn <- Lua.isfunction lua idx
|
|
|
|
unless isFn . throwIO . LuaException $ "Not a function at index " ++ show idx
|
|
|
|
Lua.pushvalue lua idx
|
|
|
|
refIdx <- Lua.ref lua Lua.registryindex
|
|
|
|
return $ LuaFilterFunction refIdx
|
2017-03-20 15:17:03 +01:00
|
|
|
|
2017-04-18 19:05:52 +02:00
|
|
|
instance StackValue LuaFilterFunction where
|
2017-03-20 15:17:03 +01:00
|
|
|
valuetype _ = Lua.TFUNCTION
|
2017-06-20 19:20:50 +02:00
|
|
|
push = pushFilterFunction
|
2017-06-20 20:51:10 +02:00
|
|
|
peek = fmap (fmap Just) . registerFilterFunction
|