aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r--src/Text/Pandoc/Lua/Global.hs108
-rw-r--r--src/Text/Pandoc/Lua/Init.hs39
2 files changed, 126 insertions, 21 deletions
diff --git a/src/Text/Pandoc/Lua/Global.hs b/src/Text/Pandoc/Lua/Global.hs
new file mode 100644
index 000000000..237c8b500
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Global.hs
@@ -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
diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index 78fb6204e..c9ee7267a 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -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"