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-11-11 11:01:38 -05:00
|
|
|
import Control.Monad (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-09-29 00:11:52 +02:00
|
|
|
import Data.IORef (IORef, newIORef, readIORef)
|
2017-11-11 11:01:38 -05:00
|
|
|
import Foreign.Lua (FromLuaStack (peek), Lua, LuaException (..),
|
2017-09-12 01:20:49 +02:00
|
|
|
Status (OK), ToLuaStack (push))
|
2017-10-27 20:28:29 -07:00
|
|
|
import Text.Pandoc.Class (CommonState, PandocIO, getCommonState, getMediaBag,
|
|
|
|
setMediaBag)
|
2017-04-14 23:24:52 +02:00
|
|
|
import Text.Pandoc.Definition
|
2017-10-27 20:28:29 -07:00
|
|
|
import Text.Pandoc.Lua.PandocModule (pushMediaBagModule, pushPandocModule)
|
2017-11-11 11:01:38 -05:00
|
|
|
import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter)
|
2017-10-27 20:28:29 -07:00
|
|
|
import Text.Pandoc.MediaBag (MediaBag)
|
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
|
2017-09-30 17:19:39 -05:00
|
|
|
commonState <- getCommonState
|
2017-09-29 00:11:52 +02:00
|
|
|
mediaBag <- getMediaBag
|
|
|
|
mediaBagRef <- liftIO (newIORef mediaBag)
|
|
|
|
res <- liftIO . Lua.runLuaEither $
|
2017-09-30 17:19:39 -05:00
|
|
|
runLuaFilter' commonState datadir filterPath format mediaBagRef pd
|
2017-09-29 00:11:52 +02:00
|
|
|
newMediaBag <- liftIO (readIORef mediaBagRef)
|
|
|
|
setMediaBag newMediaBag
|
|
|
|
return res
|
|
|
|
|
2017-09-30 17:19:39 -05:00
|
|
|
runLuaFilter' :: CommonState
|
|
|
|
-> Maybe FilePath -> FilePath -> String -> IORef MediaBag
|
2017-09-29 00:11:52 +02:00
|
|
|
-> Pandoc -> Lua Pandoc
|
2017-09-30 17:19:39 -05:00
|
|
|
runLuaFilter' commonState 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"
|
2017-09-30 17:19:39 -05:00
|
|
|
pushMediaBagModule commonState mbRef
|
2017-09-29 00:11:52 +02:00
|
|
|
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-09-12 01:20:49 +02:00
|
|
|
instance (FromLuaStack a) => FromLuaStack (Identity a) where
|
|
|
|
peek = fmap return . peek
|