aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Init.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2020-03-25 22:16:27 +0100
committerAlbert Krewinkel <albert@zeitkraut.de>2020-04-17 21:52:48 +0200
commitfb54f3d6792d2f8e7b05e458b59142f8ae6bb3e2 (patch)
treeb5403849735559bd28050fe8bccf068bdf37f48a /src/Text/Pandoc/Lua/Init.hs
parent2877ca70ecaf5b6715b38f41165974f89206d18b (diff)
downloadpandoc-fb54f3d6792d2f8e7b05e458b59142f8ae6bb3e2.tar.gz
API change: use PandocError for exceptions in Lua subsystem
The PandocError type is used throughout the Lua subsystem, all Lua functions throw an exception of this type if an error occurs. The `LuaException` type is removed and no longer exported from `Text.Pandoc.Lua`. In its place, a new constructor `PandocLuaError` is added to PandocError.
Diffstat (limited to 'src/Text/Pandoc/Lua/Init.hs')
-rw-r--r--src/Text/Pandoc/Lua/Init.hs16
1 files changed, 7 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index 757d32898..76a7d0bdc 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -9,12 +9,12 @@
Functions to initialize the Lua interpreter.
-}
module Text.Pandoc.Lua.Init
- ( LuaException (..)
- , LuaPackageParams (..)
+ ( LuaPackageParams (..)
, runLua
, luaPackageParams
) where
+import Control.Monad.Catch (try)
import Control.Monad.Trans (MonadIO (..))
import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
import Foreign.Lua (Lua)
@@ -22,28 +22,26 @@ import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
import Text.Pandoc.Class.PandocIO (PandocIO)
import Text.Pandoc.Class.PandocMonad (getCommonState, getUserDataDir,
putCommonState)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.ErrorConversion (errorConversion)
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
import Text.Pandoc.Lua.Packages (LuaPackageParams (..),
installPandocPackageSearcher)
import Text.Pandoc.Lua.Util (loadScriptFromDataDir)
-import qualified Data.Text as Text
import qualified Foreign.Lua as Lua
import qualified Foreign.Lua.Module.Text as Lua
import qualified Text.Pandoc.Definition as Pandoc
import qualified Text.Pandoc.Lua.Module.Pandoc as ModulePandoc
--- | Lua error message
-newtype LuaException = LuaException Text.Text deriving (Show)
-
-- | Run the lua interpreter, using pandoc's default way of environment
-- initialization.
-runLua :: Lua a -> PandocIO (Either LuaException a)
+runLua :: Lua a -> PandocIO (Either PandocError a)
runLua luaOp = do
luaPkgParams <- luaPackageParams
globals <- defaultGlobals
enc <- liftIO $ getForeignEncoding <* setForeignEncoding utf8
- res <- liftIO . Lua.runEither $ do
+ res <- liftIO . try . Lua.run' errorConversion $ do
setGlobals globals
initLuaState luaPkgParams
-- run the given Lua operation
@@ -56,7 +54,7 @@ runLua luaOp = do
return (opResult, st)
liftIO $ setForeignEncoding enc
case res of
- Left (Lua.Exception msg) -> return $ Left (LuaException $ Text.pack msg)
+ Left err -> return $ Left err
Right (x, newState) -> do
putCommonState newState
return $ Right x