Text.Pandoc.Lua: move globals handling to separate module
This commit is contained in:
parent
dc572e8a25
commit
7f70aaa5fa
5 changed files with 145 additions and 69 deletions
|
@ -541,6 +541,7 @@ library
|
|||
Text.Pandoc.Writers.Powerpoint.Presentation,
|
||||
Text.Pandoc.Writers.Powerpoint.Output,
|
||||
Text.Pandoc.Lua.Filter,
|
||||
Text.Pandoc.Lua.Global,
|
||||
Text.Pandoc.Lua.Init,
|
||||
Text.Pandoc.Lua.Module.MediaBag,
|
||||
Text.Pandoc.Lua.Module.Pandoc,
|
||||
|
|
|
@ -37,8 +37,9 @@ import Control.Monad ((>=>))
|
|||
import Foreign.Lua (Lua)
|
||||
import Text.Pandoc.Class (PandocIO)
|
||||
import Text.Pandoc.Definition (Pandoc)
|
||||
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
|
||||
import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter)
|
||||
import Text.Pandoc.Lua.Init (LuaException (..), runPandocLua, registerScriptPath)
|
||||
import Text.Pandoc.Lua.Init (LuaException (..), runPandocLua)
|
||||
import Text.Pandoc.Lua.Util (dofileWithTraceback)
|
||||
import Text.Pandoc.Options (ReaderOptions)
|
||||
|
||||
|
@ -49,15 +50,8 @@ import qualified Foreign.Lua as Lua
|
|||
-- interpreter.
|
||||
runLuaFilter :: ReaderOptions -> FilePath -> String
|
||||
-> Pandoc -> PandocIO (Either LuaException Pandoc)
|
||||
runLuaFilter ropts filterPath format doc =
|
||||
runPandocLua (runLuaFilter' ropts filterPath format doc)
|
||||
|
||||
runLuaFilter' :: ReaderOptions -> FilePath -> String
|
||||
-> Pandoc -> Lua Pandoc
|
||||
runLuaFilter' ropts filterPath format pd = do
|
||||
registerFormat
|
||||
registerReaderOptions
|
||||
registerScriptPath filterPath
|
||||
runLuaFilter ropts filterPath format doc = runPandocLua $ do
|
||||
setGlobals globals
|
||||
top <- Lua.gettop
|
||||
stat <- dofileWithTraceback filterPath
|
||||
if stat /= Lua.OK
|
||||
|
@ -69,15 +63,13 @@ runLuaFilter' ropts filterPath format pd = do
|
|||
luaFilters <- if newtop - top >= 1
|
||||
then Lua.peek Lua.stackTop
|
||||
else Lua.pushglobaltable *> fmap (:[]) Lua.popValue
|
||||
runAll luaFilters pd
|
||||
where
|
||||
registerFormat = do
|
||||
Lua.push format
|
||||
Lua.setglobal "FORMAT"
|
||||
runAll luaFilters doc
|
||||
|
||||
registerReaderOptions = do
|
||||
Lua.push ropts
|
||||
Lua.setglobal "PANDOC_READER_OPTIONS"
|
||||
where
|
||||
globals = [ FORMAT format
|
||||
, PANDOC_READER_OPTIONS ropts
|
||||
, PANDOC_SCRIPT_FILE filterPath
|
||||
]
|
||||
|
||||
runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
|
||||
runAll = foldr ((>=>) . walkMWithLuaFilter) return
|
||||
|
|
108
src/Text/Pandoc/Lua/Global.hs
Normal file
108
src/Text/Pandoc/Lua/Global.hs
Normal file
|
@ -0,0 +1,108 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-
|
||||
Copyright © 2017-2018 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-2018 Albert Krewinkel
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
Stability : alpha
|
||||
|
||||
Pandoc's Lua globals.
|
||||
-}
|
||||
module Text.Pandoc.Lua.Global
|
||||
( Global (..)
|
||||
, setGlobals
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.Data (Data)
|
||||
import Data.Version (Version (versionBranch))
|
||||
import Foreign.Lua (Lua, Peekable, Pushable)
|
||||
import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable
|
||||
, metatableName)
|
||||
import Paths_pandoc (version)
|
||||
import Text.Pandoc.Class (CommonState)
|
||||
import Text.Pandoc.Definition (Pandoc (Pandoc), pandocTypesVersion)
|
||||
import Text.Pandoc.Lua.StackInstances ()
|
||||
import Text.Pandoc.Lua.Util (addFunction)
|
||||
import Text.Pandoc.Options (ReaderOptions)
|
||||
|
||||
import qualified Foreign.Lua as Lua
|
||||
|
||||
-- | Permissible global Lua variables.
|
||||
data Global =
|
||||
FORMAT String
|
||||
| PANDOC_API_VERSION
|
||||
| PANDOC_DOCUMENT Pandoc
|
||||
| PANDOC_READER_OPTIONS ReaderOptions
|
||||
| PANDOC_SCRIPT_FILE FilePath
|
||||
| PANDOC_STATE CommonState
|
||||
| PANDOC_VERSION
|
||||
-- Cannot derive instance of Data because of CommonState
|
||||
|
||||
-- | Set all given globals.
|
||||
setGlobals :: [Global] -> Lua ()
|
||||
setGlobals = mapM_ setGlobal
|
||||
|
||||
setGlobal :: Global -> Lua ()
|
||||
setGlobal global = case global of
|
||||
-- This could be simplified if Global was an instance of Data.
|
||||
FORMAT format -> do
|
||||
Lua.push format
|
||||
Lua.setglobal "FORMAT"
|
||||
PANDOC_API_VERSION -> do
|
||||
Lua.push (versionBranch pandocTypesVersion)
|
||||
Lua.setglobal "PANDOC_API_VERSION"
|
||||
PANDOC_DOCUMENT doc -> do
|
||||
Lua.push (LazyPandoc doc)
|
||||
Lua.setglobal "PANDOC_DOCUMENT"
|
||||
PANDOC_READER_OPTIONS ropts -> do
|
||||
Lua.push ropts
|
||||
Lua.setglobal "PANDOC_READER_OPTIONS"
|
||||
PANDOC_SCRIPT_FILE filePath -> do
|
||||
Lua.push filePath
|
||||
Lua.setglobal "PANDOC_SCRIPT_FILE"
|
||||
PANDOC_STATE commonState -> do
|
||||
Lua.push commonState
|
||||
Lua.setglobal "PANDOC_STATE"
|
||||
PANDOC_VERSION -> do
|
||||
Lua.push (versionBranch version)
|
||||
Lua.setglobal "PANDOC_VERSION"
|
||||
|
||||
-- | Readonly and lazy pandoc objects.
|
||||
newtype LazyPandoc = LazyPandoc Pandoc
|
||||
deriving (Data)
|
||||
|
||||
instance Pushable LazyPandoc where
|
||||
push lazyDoc = pushAnyWithMetatable pushPandocMetatable lazyDoc
|
||||
where
|
||||
pushPandocMetatable = ensureUserdataMetatable (metatableName lazyDoc) $
|
||||
addFunction "__index" indexLazyPandoc
|
||||
|
||||
instance Peekable LazyPandoc where
|
||||
peek = Lua.peekAny
|
||||
|
||||
indexLazyPandoc :: LazyPandoc -> String -> Lua Lua.NumResults
|
||||
indexLazyPandoc (LazyPandoc (Pandoc meta blks)) field = 1 <$
|
||||
case field of
|
||||
"blocks" -> Lua.push blks
|
||||
"meta" -> Lua.push meta
|
||||
_ -> Lua.pushnil
|
|
@ -32,20 +32,17 @@ module Text.Pandoc.Lua.Init
|
|||
, runPandocLua
|
||||
, initLuaState
|
||||
, luaPackageParams
|
||||
, registerScriptPath
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad.Trans (MonadIO (..))
|
||||
import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
|
||||
import Data.IORef (newIORef, readIORef)
|
||||
import Data.Version (Version (versionBranch))
|
||||
import Foreign.Lua (Lua)
|
||||
import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
|
||||
import Paths_pandoc (version)
|
||||
import Text.Pandoc.Class (CommonState, PandocIO, getCommonState,
|
||||
getUserDataDir, getMediaBag, setMediaBag)
|
||||
import Text.Pandoc.Definition (pandocTypesVersion)
|
||||
import Text.Pandoc.Class (PandocIO, getCommonState, getUserDataDir,
|
||||
getMediaBag, setMediaBag)
|
||||
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
|
||||
import Text.Pandoc.Lua.Packages (LuaPackageParams (..),
|
||||
installPandocPackageSearcher)
|
||||
import Text.Pandoc.Lua.Util (loadScriptFromDataDir)
|
||||
|
@ -61,11 +58,12 @@ newtype LuaException = LuaException String deriving (Show)
|
|||
-- initialization.
|
||||
runPandocLua :: Lua a -> PandocIO (Either LuaException a)
|
||||
runPandocLua luaOp = do
|
||||
commonState <- getCommonState
|
||||
luaPkgParams <- luaPackageParams
|
||||
globals <- defaultGlobals
|
||||
enc <- liftIO $ getForeignEncoding <* setForeignEncoding utf8
|
||||
res <- liftIO . Lua.runEither $ do
|
||||
initLuaState commonState luaPkgParams
|
||||
setGlobals globals
|
||||
initLuaState luaPkgParams
|
||||
luaOp
|
||||
liftIO $ setForeignEncoding enc
|
||||
newMediaBag <- liftIO (readIORef (luaPkgMediaBag luaPkgParams))
|
||||
|
@ -74,6 +72,16 @@ runPandocLua luaOp = do
|
|||
Left (Lua.Exception msg) -> Left (LuaException msg)
|
||||
Right x -> Right x
|
||||
|
||||
-- | Global variables which should always be set.
|
||||
defaultGlobals :: PandocIO [Global]
|
||||
defaultGlobals = do
|
||||
commonState <- getCommonState
|
||||
return
|
||||
[ PANDOC_API_VERSION
|
||||
, PANDOC_STATE commonState
|
||||
, PANDOC_VERSION
|
||||
]
|
||||
|
||||
-- | Generate parameters required to setup pandoc's lua environment.
|
||||
luaPackageParams :: PandocIO LuaPackageParams
|
||||
luaPackageParams = do
|
||||
|
@ -87,25 +95,14 @@ luaPackageParams = do
|
|||
}
|
||||
|
||||
-- Initialize the lua state with all required values
|
||||
initLuaState :: CommonState -> LuaPackageParams -> Lua ()
|
||||
initLuaState commonState luaPkgParams = do
|
||||
initLuaState :: LuaPackageParams -> Lua ()
|
||||
initLuaState luaPkgParams = do
|
||||
Lua.openlibs
|
||||
Lua.preloadTextModule "text"
|
||||
Lua.push (versionBranch version)
|
||||
Lua.setglobal "PANDOC_VERSION"
|
||||
Lua.push (versionBranch pandocTypesVersion)
|
||||
Lua.setglobal "PANDOC_API_VERSION"
|
||||
Lua.push commonState
|
||||
Lua.setglobal "PANDOC_STATE"
|
||||
installPandocPackageSearcher luaPkgParams
|
||||
loadScriptFromDataDir (luaPkgDataDir luaPkgParams) "init.lua"
|
||||
putConstructorsInRegistry
|
||||
|
||||
registerScriptPath :: FilePath -> Lua ()
|
||||
registerScriptPath fp = do
|
||||
Lua.push fp
|
||||
Lua.setglobal "PANDOC_SCRIPT_FILE"
|
||||
|
||||
putConstructorsInRegistry :: Lua ()
|
||||
putConstructorsInRegistry = do
|
||||
Lua.getglobal "pandoc"
|
||||
|
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{- Copyright (C) 2012-2018 John MacFarlane <jgm@berkeley.edu>
|
||||
|
@ -36,21 +35,18 @@ import Control.Arrow ((***))
|
|||
import Control.Exception
|
||||
import Control.Monad (when)
|
||||
import Data.Char (toLower)
|
||||
import Data.Data (Data)
|
||||
import Data.List (intersperse)
|
||||
import qualified Data.Map as M
|
||||
import Data.Text (Text, pack)
|
||||
import Data.Typeable
|
||||
import Foreign.Lua (Lua, Peekable, Pushable)
|
||||
import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable
|
||||
, metatableName)
|
||||
import Foreign.Lua (Lua, Pushable)
|
||||
import Text.Pandoc.Class (PandocIO)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Error
|
||||
import Text.Pandoc.Lua.Init (LuaException (LuaException), runPandocLua,
|
||||
registerScriptPath)
|
||||
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
|
||||
import Text.Pandoc.Lua.Init (LuaException (LuaException), runPandocLua)
|
||||
import Text.Pandoc.Lua.StackInstances ()
|
||||
import Text.Pandoc.Lua.Util (addField, addFunction, dofileWithTraceback)
|
||||
import Text.Pandoc.Lua.Util (addField, dofileWithTraceback)
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Templates
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
|
@ -109,32 +105,14 @@ data PandocLuaException = PandocLuaException String
|
|||
|
||||
instance Exception PandocLuaException
|
||||
|
||||
-- | Readonly and lazy pandoc objects.
|
||||
newtype LazyPandoc = LazyPandoc Pandoc
|
||||
deriving (Data)
|
||||
|
||||
instance Pushable LazyPandoc where
|
||||
push lazyDoc = pushAnyWithMetatable pushPandocMetatable lazyDoc
|
||||
where
|
||||
pushPandocMetatable = ensureUserdataMetatable (metatableName lazyDoc) $
|
||||
addFunction "__index" indexLazyPandoc
|
||||
|
||||
instance Peekable LazyPandoc where
|
||||
peek = Lua.peekAny
|
||||
|
||||
indexLazyPandoc :: LazyPandoc -> String -> Lua Lua.NumResults
|
||||
indexLazyPandoc (LazyPandoc (Pandoc meta blks)) field = 1 <$
|
||||
case field of
|
||||
"blocks" -> Lua.push blks
|
||||
"meta" -> Lua.push meta
|
||||
_ -> Lua.pushnil
|
||||
|
||||
-- | Convert Pandoc to custom markup.
|
||||
writeCustom :: FilePath -> WriterOptions -> Pandoc -> PandocIO Text
|
||||
writeCustom luaFile opts doc@(Pandoc meta _) = do
|
||||
let globals = [ PANDOC_DOCUMENT doc
|
||||
, PANDOC_SCRIPT_FILE luaFile
|
||||
]
|
||||
res <- runPandocLua $ do
|
||||
Lua.push (LazyPandoc doc) *> Lua.setglobal "PANDOC_DOCUMENT"
|
||||
registerScriptPath luaFile
|
||||
setGlobals globals
|
||||
stat <- dofileWithTraceback luaFile
|
||||
-- check for error in lua script (later we'll change the return type
|
||||
-- to handle this more gracefully):
|
||||
|
|
Loading…
Add table
Reference in a new issue