Lua modules: move to dedicated submodule
The Haskell module defining the Lua `pandoc` module is moved to Text.Pandoc.Lua.Module.Pandoc. Change: minor
This commit is contained in:
parent
6ec7e39b4c
commit
ab3c506584
5 changed files with 38 additions and 35 deletions
|
@ -523,8 +523,8 @@ library
|
||||||
Text.Pandoc.Readers.Org.Shared,
|
Text.Pandoc.Readers.Org.Shared,
|
||||||
Text.Pandoc.Lua.Filter,
|
Text.Pandoc.Lua.Filter,
|
||||||
Text.Pandoc.Lua.Init,
|
Text.Pandoc.Lua.Init,
|
||||||
|
Text.Pandoc.Lua.Module.Pandoc,
|
||||||
Text.Pandoc.Lua.Packages,
|
Text.Pandoc.Lua.Packages,
|
||||||
Text.Pandoc.Lua.PandocModule,
|
|
||||||
Text.Pandoc.Lua.StackInstances,
|
Text.Pandoc.Lua.StackInstances,
|
||||||
Text.Pandoc.Lua.Util,
|
Text.Pandoc.Lua.Util,
|
||||||
Text.Pandoc.CSS,
|
Text.Pandoc.CSS,
|
||||||
|
|
|
@ -39,7 +39,7 @@ import Text.Pandoc.Class (PandocIO)
|
||||||
import Text.Pandoc.Definition (Pandoc)
|
import Text.Pandoc.Definition (Pandoc)
|
||||||
import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter)
|
import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter)
|
||||||
import Text.Pandoc.Lua.Init (runPandocLua)
|
import Text.Pandoc.Lua.Init (runPandocLua)
|
||||||
import Text.Pandoc.Lua.PandocModule (pushPandocModule) -- TODO: remove
|
import Text.Pandoc.Lua.Module.Pandoc (pushModule) -- TODO: remove
|
||||||
import qualified Foreign.Lua as Lua
|
import qualified Foreign.Lua as Lua
|
||||||
|
|
||||||
-- | Run the Lua filter in @filterPath@ for a transformation to target
|
-- | Run the Lua filter in @filterPath@ for a transformation to target
|
||||||
|
@ -81,3 +81,7 @@ pushGlobalFilter = do
|
||||||
|
|
||||||
runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
|
runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
|
||||||
runAll = foldr ((>=>) . walkMWithLuaFilter) return
|
runAll = foldr ((>=>) . walkMWithLuaFilter) return
|
||||||
|
|
||||||
|
-- | DEPRECATED: Push the pandoc module to the Lua Stack.
|
||||||
|
pushPandocModule :: Maybe FilePath -> Lua Lua.NumResults
|
||||||
|
pushPandocModule = pushModule
|
||||||
|
|
|
@ -17,7 +17,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||||
-}
|
-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{- |
|
{- |
|
||||||
Module : Text.Pandoc.Lua.PandocModule
|
Module : Text.Pandoc.Lua.Module.Pandoc
|
||||||
Copyright : Copyright © 2017 Albert Krewinkel
|
Copyright : Copyright © 2017 Albert Krewinkel
|
||||||
License : GNU GPL, version 2 or above
|
License : GNU GPL, version 2 or above
|
||||||
|
|
||||||
|
@ -26,8 +26,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||||
|
|
||||||
Pandoc module for lua.
|
Pandoc module for lua.
|
||||||
-}
|
-}
|
||||||
module Text.Pandoc.Lua.PandocModule
|
module Text.Pandoc.Lua.Module.Pandoc
|
||||||
( pushPandocModule
|
( pushModule
|
||||||
, pushMediaBagModule
|
, pushMediaBagModule
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -44,7 +44,8 @@ import Text.Pandoc.Class (CommonState (..), fetchItem, putCommonState,
|
||||||
import Text.Pandoc.Definition (Block, Inline)
|
import Text.Pandoc.Definition (Block, Inline)
|
||||||
import Text.Pandoc.Lua.Filter (walkInlines, walkBlocks, LuaFilter)
|
import Text.Pandoc.Lua.Filter (walkInlines, walkBlocks, LuaFilter)
|
||||||
import Text.Pandoc.Lua.StackInstances ()
|
import Text.Pandoc.Lua.StackInstances ()
|
||||||
import Text.Pandoc.Lua.Util (addFunction, addValue, loadScriptFromDataDir)
|
import Text.Pandoc.Lua.Util (OrNil (toMaybe), addFunction, addValue,
|
||||||
|
loadScriptFromDataDir, raiseError)
|
||||||
import Text.Pandoc.Walk (Walkable)
|
import Text.Pandoc.Walk (Walkable)
|
||||||
import Text.Pandoc.MIME (MimeType)
|
import Text.Pandoc.MIME (MimeType)
|
||||||
import Text.Pandoc.Options (ReaderOptions (readerExtensions))
|
import Text.Pandoc.Options (ReaderOptions (readerExtensions))
|
||||||
|
@ -58,8 +59,8 @@ import qualified Text.Pandoc.MediaBag as MB
|
||||||
|
|
||||||
-- | Push the "pandoc" on the lua stack. Requires the `list` module to be
|
-- | Push the "pandoc" on the lua stack. Requires the `list` module to be
|
||||||
-- loaded.
|
-- loaded.
|
||||||
pushPandocModule :: Maybe FilePath -> Lua NumResults
|
pushModule :: Maybe FilePath -> Lua NumResults
|
||||||
pushPandocModule datadir = do
|
pushModule datadir = do
|
||||||
loadScriptFromDataDir datadir "pandoc.lua"
|
loadScriptFromDataDir datadir "pandoc.lua"
|
||||||
addFunction "read" readDoc
|
addFunction "read" readDoc
|
||||||
addFunction "pipe" pipeFn
|
addFunction "pipe" pipeFn
|
||||||
|
@ -91,10 +92,6 @@ readDoc content formatSpecOrNil = do
|
||||||
Right pd -> (1 :: NumResults) <$ Lua.push pd -- success, push Pandoc
|
Right pd -> (1 :: NumResults) <$ Lua.push pd -- success, push Pandoc
|
||||||
Left s -> raiseError (show s) -- error while reading
|
Left s -> raiseError (show s) -- error while reading
|
||||||
_ -> raiseError "Only string formats are supported at the moment."
|
_ -> raiseError "Only string formats are supported at the moment."
|
||||||
where
|
|
||||||
raiseError s = do
|
|
||||||
Lua.push s
|
|
||||||
fromIntegral <$> Lua.lerror
|
|
||||||
|
|
||||||
--
|
--
|
||||||
-- MediaBag submodule
|
-- MediaBag submodule
|
||||||
|
@ -122,12 +119,8 @@ pipeFn :: String
|
||||||
pipeFn command args input = do
|
pipeFn command args input = do
|
||||||
(ec, output) <- liftIO $ pipeProcess Nothing command args input
|
(ec, output) <- liftIO $ pipeProcess Nothing command args input
|
||||||
case ec of
|
case ec of
|
||||||
ExitSuccess -> do
|
ExitSuccess -> 1 <$ Lua.push output
|
||||||
Lua.push output
|
ExitFailure n -> raiseError (PipeError command n output)
|
||||||
return 1
|
|
||||||
ExitFailure n -> do
|
|
||||||
Lua.push (PipeError command n output)
|
|
||||||
fromIntegral <$> Lua.lerror
|
|
||||||
|
|
||||||
data PipeError = PipeError
|
data PipeError = PipeError
|
||||||
{ pipeErrorCommand :: String
|
{ pipeErrorCommand :: String
|
||||||
|
@ -218,16 +211,3 @@ fetch commonState mbRef src = do
|
||||||
Lua.push $ fromMaybe "" mimeType
|
Lua.push $ fromMaybe "" mimeType
|
||||||
Lua.push bs
|
Lua.push bs
|
||||||
return 2 -- returns 2 values: contents, mimetype
|
return 2 -- returns 2 values: contents, mimetype
|
||||||
|
|
||||||
--
|
|
||||||
-- Helper types
|
|
||||||
--
|
|
||||||
|
|
||||||
newtype OrNil a = OrNil { toMaybe :: Maybe a }
|
|
||||||
|
|
||||||
instance FromLuaStack a => FromLuaStack (OrNil a) where
|
|
||||||
peek idx = do
|
|
||||||
noValue <- Lua.isnoneornil idx
|
|
||||||
if noValue
|
|
||||||
then return (OrNil Nothing)
|
|
||||||
else OrNil . Just <$> Lua.peek idx
|
|
|
@ -38,10 +38,11 @@ import Data.IORef (IORef)
|
||||||
import Foreign.Lua (Lua, NumResults, liftIO)
|
import Foreign.Lua (Lua, NumResults, liftIO)
|
||||||
import Text.Pandoc.Class (CommonState, readDataFile, runIO, setUserDataDir)
|
import Text.Pandoc.Class (CommonState, readDataFile, runIO, setUserDataDir)
|
||||||
import Text.Pandoc.MediaBag (MediaBag)
|
import Text.Pandoc.MediaBag (MediaBag)
|
||||||
import Text.Pandoc.Lua.PandocModule (pushPandocModule, pushMediaBagModule)
|
import Text.Pandoc.Lua.Module.Pandoc (pushMediaBagModule)
|
||||||
import Text.Pandoc.Lua.Util (dostring')
|
import Text.Pandoc.Lua.Util (dostring')
|
||||||
|
|
||||||
import qualified Foreign.Lua as Lua
|
import qualified Foreign.Lua as Lua
|
||||||
|
import Text.Pandoc.Lua.Module.Pandoc as Pandoc
|
||||||
|
|
||||||
-- | Parameters used to create lua packages/modules.
|
-- | Parameters used to create lua packages/modules.
|
||||||
data LuaPackageParams = LuaPackageParams
|
data LuaPackageParams = LuaPackageParams
|
||||||
|
@ -72,7 +73,7 @@ pandocPackageSearcher :: LuaPackageParams -> String -> Lua NumResults
|
||||||
pandocPackageSearcher luaPkgParams pkgName =
|
pandocPackageSearcher luaPkgParams pkgName =
|
||||||
case pkgName of
|
case pkgName of
|
||||||
"pandoc" -> let datadir = luaPkgDataDir luaPkgParams
|
"pandoc" -> let datadir = luaPkgDataDir luaPkgParams
|
||||||
in pushWrappedHsFun (pushPandocModule datadir)
|
in pushWrappedHsFun (Pandoc.pushModule datadir)
|
||||||
"pandoc.mediabag" -> let st = luaPkgCommonState luaPkgParams
|
"pandoc.mediabag" -> let st = luaPkgCommonState luaPkgParams
|
||||||
mbRef = luaPkgMediaBag luaPkgParams
|
mbRef = luaPkgMediaBag luaPkgParams
|
||||||
in pushWrappedHsFun (pushMediaBagModule st mbRef)
|
in pushWrappedHsFun (pushMediaBagModule st mbRef)
|
||||||
|
|
|
@ -36,6 +36,8 @@ module Text.Pandoc.Lua.Util
|
||||||
, getRawInt
|
, getRawInt
|
||||||
, setRawInt
|
, setRawInt
|
||||||
, addRawInt
|
, addRawInt
|
||||||
|
, raiseError
|
||||||
|
, OrNil (..)
|
||||||
, PushViaCall
|
, PushViaCall
|
||||||
, pushViaCall
|
, pushViaCall
|
||||||
, pushViaConstructor
|
, pushViaConstructor
|
||||||
|
@ -45,8 +47,8 @@ module Text.Pandoc.Lua.Util
|
||||||
|
|
||||||
import Control.Monad (when)
|
import Control.Monad (when)
|
||||||
import Data.ByteString.Char8 (unpack)
|
import Data.ByteString.Char8 (unpack)
|
||||||
import Foreign.Lua (FromLuaStack (..), ToHaskellFunction, Lua, NumArgs,
|
import Foreign.Lua (FromLuaStack (..), NumResults, Lua, NumArgs, StackIndex,
|
||||||
StackIndex, ToLuaStack (..), getglobal')
|
ToLuaStack (..), ToHaskellFunction, getglobal')
|
||||||
import Foreign.Lua.Api (Status, call, pop, rawget, rawgeti, rawset, rawseti)
|
import Foreign.Lua.Api (Status, call, pop, rawget, rawgeti, rawset, rawseti)
|
||||||
import Text.Pandoc.Class (readDataFile, runIOorExplode, setUserDataDir)
|
import Text.Pandoc.Class (readDataFile, runIOorExplode, setUserDataDir)
|
||||||
|
|
||||||
|
@ -99,6 +101,22 @@ setRawInt idx key value = do
|
||||||
addRawInt :: ToLuaStack a => Int -> a -> Lua ()
|
addRawInt :: ToLuaStack a => Int -> a -> Lua ()
|
||||||
addRawInt = setRawInt (-1)
|
addRawInt = setRawInt (-1)
|
||||||
|
|
||||||
|
raiseError :: ToLuaStack a => a -> Lua NumResults
|
||||||
|
raiseError e = do
|
||||||
|
Lua.push e
|
||||||
|
fromIntegral <$> Lua.lerror
|
||||||
|
|
||||||
|
-- | Newtype wrapper intended to be used for optional Lua values. Nesting this
|
||||||
|
-- type is strongly discouraged and will likely lead to a wrong result.
|
||||||
|
newtype OrNil a = OrNil { toMaybe :: Maybe a }
|
||||||
|
|
||||||
|
instance FromLuaStack a => FromLuaStack (OrNil a) where
|
||||||
|
peek idx = do
|
||||||
|
noValue <- Lua.isnoneornil idx
|
||||||
|
if noValue
|
||||||
|
then return (OrNil Nothing)
|
||||||
|
else OrNil . Just <$> Lua.peek idx
|
||||||
|
|
||||||
-- | Helper class for pushing a single value to the stack via a lua function.
|
-- | Helper class for pushing a single value to the stack via a lua function.
|
||||||
-- See @pushViaCall@.
|
-- See @pushViaCall@.
|
||||||
class PushViaCall a where
|
class PushViaCall a where
|
||||||
|
|
Loading…
Reference in a new issue