Lua subsystem and custom writers: generalize types from PandocIO...
to any instance of PandocMonad and MonadIO. This involves an API change, since the type of runLua is now (PandocMonad m, MonadIO m) => Lua a -> m (Either PandocError a)
This commit is contained in:
parent
7ff06a8c43
commit
0df003b099
3 changed files with 8 additions and 8 deletions
|
@ -18,8 +18,7 @@ import Control.Monad.Trans (MonadIO (..))
|
|||
import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
|
||||
import Foreign.Lua (Lua)
|
||||
import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
|
||||
import Text.Pandoc.Class.PandocMonad (readDataFile)
|
||||
import Text.Pandoc.Class.PandocIO (PandocIO)
|
||||
import Text.Pandoc.Class.PandocMonad (readDataFile, PandocMonad)
|
||||
import Text.Pandoc.Error (PandocError)
|
||||
import Text.Pandoc.Lua.Packages (installPandocPackageSearcher)
|
||||
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, runPandocLua)
|
||||
|
@ -30,7 +29,7 @@ import qualified Text.Pandoc.Lua.Module.Pandoc as ModulePandoc
|
|||
|
||||
-- | Run the lua interpreter, using pandoc's default way of environment
|
||||
-- initialization.
|
||||
runLua :: Lua a -> PandocIO (Either PandocError a)
|
||||
runLua :: (PandocMonad m, MonadIO m) => Lua a -> m (Either PandocError a)
|
||||
runLua luaOp = do
|
||||
enc <- liftIO $ getForeignEncoding <* setForeignEncoding utf8
|
||||
res <- runPandocLua . try $ do
|
||||
|
|
|
@ -30,7 +30,6 @@ import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow)
|
|||
import Control.Monad.Except (MonadError (catchError, throwError))
|
||||
import Control.Monad.IO.Class (MonadIO (liftIO))
|
||||
import Foreign.Lua (Lua (..), NumResults, Pushable, ToHaskellFunction)
|
||||
import Text.Pandoc.Class.PandocIO (PandocIO)
|
||||
import Text.Pandoc.Class.PandocMonad (PandocMonad (..), readDefaultDataFile)
|
||||
import Text.Pandoc.Error (PandocError (PandocLuaError))
|
||||
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
|
||||
|
@ -59,7 +58,7 @@ liftPandocLua = PandocLua
|
|||
|
||||
-- | Evaluate a @'PandocLua'@ computation, running all contained Lua
|
||||
-- operations..
|
||||
runPandocLua :: PandocLua a -> PandocIO a
|
||||
runPandocLua :: (PandocMonad m, MonadIO m) => PandocLua a -> m a
|
||||
runPandocLua pLua = do
|
||||
origState <- getCommonState
|
||||
globals <- defaultGlobals
|
||||
|
@ -103,7 +102,7 @@ loadDefaultModule name = do
|
|||
throwError $ PandocLuaError (T.pack err)
|
||||
|
||||
-- | Global variables which should always be set.
|
||||
defaultGlobals :: PandocIO [Global]
|
||||
defaultGlobals :: PandocMonad m => m [Global]
|
||||
defaultGlobals = do
|
||||
commonState <- getCommonState
|
||||
return
|
||||
|
|
|
@ -22,11 +22,12 @@ import qualified Data.Text as T
|
|||
import Data.Text (Text, pack)
|
||||
import Foreign.Lua (Lua, Pushable)
|
||||
import Text.DocLayout (render, literal)
|
||||
import Text.Pandoc.Class.PandocIO (PandocIO)
|
||||
import Control.Monad.IO.Class (MonadIO)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Lua (Global (..), runLua, setGlobals)
|
||||
import Text.Pandoc.Lua.Util (addField, dofileWithTraceback)
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Class (PandocMonad)
|
||||
import Text.Pandoc.Templates (renderTemplate)
|
||||
import Text.Pandoc.Writers.Shared
|
||||
|
||||
|
@ -79,7 +80,8 @@ instance (Pushable a, Pushable b) => Pushable (KeyValue a b) where
|
|||
Lua.rawset (Lua.nthFromTop 3)
|
||||
|
||||
-- | Convert Pandoc to custom markup.
|
||||
writeCustom :: FilePath -> WriterOptions -> Pandoc -> PandocIO Text
|
||||
writeCustom :: (PandocMonad m, MonadIO m)
|
||||
=> FilePath -> WriterOptions -> Pandoc -> m Text
|
||||
writeCustom luaFile opts doc@(Pandoc meta _) = do
|
||||
let globals = [ PANDOC_DOCUMENT doc
|
||||
, PANDOC_SCRIPT_FILE luaFile
|
||||
|
|
Loading…
Add table
Reference in a new issue