diff options
| author | Albert Krewinkel <[email protected]> | 2022-10-06 12:57:46 +0200 |
|---|---|---|
| committer | Albert Krewinkel <[email protected]> | 2022-10-06 13:45:55 +0200 |
| commit | afbf732a830074cb01804d9808cc8334a1572c8e (patch) | |
| tree | 28f9780e98ce25e450ef3ddbccb2116dba89e3b0 /pandoc-lua-engine | |
| parent | 3206506696d30063c4999dbcb3ce9080018740d2 (diff) | |
Lua: cleanup module dependencies
Ensures a cleaner module dependency graph.
Diffstat (limited to 'pandoc-lua-engine')
10 files changed, 61 insertions, 93 deletions
diff --git a/pandoc-lua-engine/pandoc-lua-engine.cabal b/pandoc-lua-engine/pandoc-lua-engine.cabal index 623ba1363..b8f3abbd1 100644 --- a/pandoc-lua-engine/pandoc-lua-engine.cabal +++ b/pandoc-lua-engine/pandoc-lua-engine.cabal @@ -60,8 +60,7 @@ library import: common-options hs-source-dirs: src exposed-modules: Text.Pandoc.Lua - other-modules: Text.Pandoc.Lua.ErrorConversion - , Text.Pandoc.Lua.Filter + other-modules: Text.Pandoc.Lua.Filter , Text.Pandoc.Lua.Global , Text.Pandoc.Lua.Init , Text.Pandoc.Lua.Marshal.CommonState diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/ErrorConversion.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/ErrorConversion.hs deleted file mode 100644 index 3968eba84..000000000 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/ErrorConversion.hs +++ /dev/null @@ -1,40 +0,0 @@ -{-# OPTIONS_GHC -fno-warn-orphans #-} -{- | - Module : Text.Pandoc.Lua.ErrorConversion - Copyright : © 2020-2022 Albert Krewinkel - License : GNU GPL, version 2 or above - - Maintainer : Albert Krewinkel <[email protected]> - Stability : alpha - -Define how Lua errors are converted into @'PandocError'@ Haskell -exceptions, and /vice versa/. --} -module Text.Pandoc.Lua.ErrorConversion - ( addContextToException - ) where - -import HsLua (LuaError, LuaE, resultToEither, runPeek, top) -import Text.Pandoc.Error (PandocError (PandocLuaError)) -import Text.Pandoc.Lua.Marshal.PandocError (pushPandocError, peekPandocError) - -import qualified Data.Text as T -import qualified HsLua as Lua - -addContextToException :: () -addContextToException = undefined - --- | Retrieve a @'PandocError'@ from the Lua stack. -popPandocError :: LuaE PandocError PandocError -popPandocError = do - errResult <- runPeek $ peekPandocError top - case resultToEither errResult of - Right x -> return x - Left err -> return $ PandocLuaError (T.pack err) - --- Ensure conversions between Lua errors and 'PandocError' exceptions --- are possible. -instance LuaError PandocError where - popException = popPandocError - pushException = pushPandocError - luaException = PandocLuaError . T.pack diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs index c019095f8..6e7dc0fba 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs @@ -19,11 +19,11 @@ import Control.Monad ((>=>), (<$!>)) import HsLua as Lua import Text.Pandoc.Definition import Text.Pandoc.Filter (Environment (..)) -import Text.Pandoc.Lua.ErrorConversion () import Text.Pandoc.Lua.Marshal.AST import Text.Pandoc.Lua.Marshal.Filter import Text.Pandoc.Lua.Global (Global (..), setGlobals) import Text.Pandoc.Lua.Init (runLua) +import Text.Pandoc.Lua.PandocLua () import Control.Exception (throw) import qualified Data.Text as T import Text.Pandoc.Class (PandocMonad) diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs index 702ba7bd5..5ec7ced64 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs @@ -23,7 +23,7 @@ import Text.Pandoc.Lua.Marshal.CommonState (pushCommonState) import Text.Pandoc.Lua.Marshal.Pandoc (pushPandoc) import Text.Pandoc.Lua.Marshal.ReaderOptions (pushReaderOptionsReadonly) import Text.Pandoc.Lua.Marshal.WriterOptions (pushWriterOptions) -import Text.Pandoc.Lua.Orphans () +import Text.Pandoc.Lua.PandocLua () import Text.Pandoc.Options (ReaderOptions, WriterOptions) import Text.Pandoc.Shared (pandocVersion) diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs index 98a2f5c7b..ffe77bfde 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs @@ -1,5 +1,6 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} {- | Module : Text.Pandoc.Lua Copyright : Copyright © 2017-2022 Albert Krewinkel @@ -22,11 +23,12 @@ import Control.Monad.Trans (MonadIO (..)) import Data.Maybe (catMaybes) import HsLua as Lua hiding (status, try) import HsLua.Core.Run as Lua -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad (..)) import Text.Pandoc.Data (readDataFile) import Text.Pandoc.Error (PandocError (PandocLuaError)) +import Text.Pandoc.Lua.Global (Global (..), setGlobals) import Text.Pandoc.Lua.Marshal.List (newListMetatable, pushListModule) -import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, runPandocLuaWith) +import Text.Pandoc.Lua.PandocLua (PandocLua (..), liftPandocLua) import qualified Data.ByteString.Char8 as Char8 import qualified Data.Text as T import qualified Lua.LPeg as LPeg @@ -177,3 +179,31 @@ initLuaState = do initJsonMetatable :: PandocLua () initJsonMetatable = liftPandocLua $ do newListMetatable HsLua.Aeson.jsonarray (pure ()) + +-- | Evaluate a @'PandocLua'@ computation, running all contained Lua +-- operations. +runPandocLuaWith :: (PandocMonad m, MonadIO m) + => (forall b. LuaE PandocError b -> IO b) + -> PandocLua a + -> m a +runPandocLuaWith runner pLua = do + origState <- getCommonState + globals <- defaultGlobals + (result, newState) <- liftIO . runner . unPandocLua $ do + putCommonState origState + liftPandocLua $ setGlobals globals + r <- pLua + c <- getCommonState + return (r, c) + putCommonState newState + return result + +-- | Global variables which should always be set. +defaultGlobals :: PandocMonad m => m [Global] +defaultGlobals = do + commonState <- getCommonState + return + [ PANDOC_API_VERSION + , PANDOC_STATE commonState + , PANDOC_VERSION + ] diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs index 8fa0485fc..7eb66b3ca 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs @@ -15,8 +15,8 @@ import HsLua import Text.Pandoc.Error (PandocError) import Text.Pandoc.Extensions ( getAllExtensions, getDefaultExtensions ) -import Text.Pandoc.Lua.ErrorConversion () import Text.Pandoc.Lua.Marshal.Extensions (pushExtensions) +import Text.Pandoc.Lua.PandocLua () import qualified Data.Text as T diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs index b8d45d93e..7d9ad6784 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs @@ -17,7 +17,7 @@ import HsLua ( Module (..), (###), (<#>), (=#>) , defun, functionResult, parameter) import HsLua.Module.Version (peekVersionFuzzy, pushVersion) import Text.Pandoc.Error (PandocError) -import Text.Pandoc.Lua.ErrorConversion () +import Text.Pandoc.Lua.PandocLua () -- | Push the pandoc.types module on the Lua stack. documentedModule :: Module PandocError diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs index 33349870c..16305b76e 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs @@ -204,7 +204,7 @@ stringify idx = forcePeek . retrieving "stringifyable element" $ -- | Converts an old/simple table into a normal table block element. from_simple_table :: SimpleTable -> LuaE PandocError NumResults from_simple_table (SimpleTable capt aligns widths head' body) = do - Lua.push $ Table + pushBlock $ Table nullAttr (Caption Nothing [Plain capt | not (null capt)]) (zipWith (\a w -> (a, toColWidth w)) aligns widths) diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Orphans.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Orphans.hs index 62b54d051..db58349d2 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Orphans.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Orphans.hs @@ -23,7 +23,6 @@ import Text.Pandoc.Lua.Marshal.Context () import Text.Pandoc.Lua.Marshal.PandocError() import Text.Pandoc.Lua.Marshal.ReaderOptions () import Text.Pandoc.Lua.Marshal.Sources (pushSources) -import Text.Pandoc.Lua.ErrorConversion () import Text.Pandoc.Sources (Sources) instance Pushable Pandoc where diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs index 6564ec91d..d922dfe1c 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs @@ -4,24 +4,18 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Text.Pandoc.Lua.PandocLua - Copyright : Copyright © 2020-2022 Albert Krewinkel - License : GNU GPL, version 2 or above - + Copyright : © 2020-2022 Albert Krewinkel + License : GPL-2.0-or-later Maintainer : Albert Krewinkel <[email protected]> - Stability : alpha PandocMonad instance which allows execution of Lua operations and which uses Lua to handle state. -} module Text.Pandoc.Lua.PandocLua ( PandocLua (..) - , runPandocLua - , runPandocLuaWith , liftPandocLua ) where @@ -30,11 +24,12 @@ import Control.Monad.Except (MonadError (catchError, throwError)) import Control.Monad.IO.Class (MonadIO) import HsLua as Lua import Text.Pandoc.Class (PandocMonad (..)) -import Text.Pandoc.Error (PandocError) -import Text.Pandoc.Lua.Global (Global (..), setGlobals) -import Text.Pandoc.Lua.Marshal.CommonState (peekCommonState) +import Text.Pandoc.Error (PandocError (..)) +import Text.Pandoc.Lua.Marshal.CommonState (peekCommonState, pushCommonState) +import Text.Pandoc.Lua.Marshal.PandocError (peekPandocError, pushPandocError) import qualified Control.Monad.Catch as Catch +import qualified Data.Text as T import qualified Text.Pandoc.Class.IO as IO -- | Type providing access to both, pandoc and Lua operations. @@ -53,43 +48,12 @@ newtype PandocLua a = PandocLua { unPandocLua :: LuaE PandocError a } liftPandocLua :: LuaE PandocError a -> PandocLua a liftPandocLua = PandocLua --- | Evaluate a @'PandocLua'@ computation, running all contained Lua --- operations.. -runPandocLua :: (PandocMonad m, MonadIO m) => PandocLua a -> m a -runPandocLua = runPandocLuaWith Lua.run - -runPandocLuaWith :: (PandocMonad m, MonadIO m) - => (forall b. LuaE PandocError b -> IO b) - -> PandocLua a - -> m a -runPandocLuaWith runner pLua = do - origState <- getCommonState - globals <- defaultGlobals - (result, newState) <- liftIO . runner . unPandocLua $ do - putCommonState origState - liftPandocLua $ setGlobals globals - r <- pLua - c <- getCommonState - return (r, c) - putCommonState newState - return result - instance {-# OVERLAPPING #-} Exposable PandocError (PandocLua NumResults) where partialApply _narg = liftLua . unPandocLua instance Pushable a => Exposable PandocError (PandocLua a) where partialApply _narg x = 1 <$ (liftLua (unPandocLua x >>= Lua.push)) --- | Global variables which should always be set. -defaultGlobals :: PandocMonad m => m [Global] -defaultGlobals = do - commonState <- getCommonState - return - [ PANDOC_API_VERSION - , PANDOC_STATE commonState - , PANDOC_VERSION - ] - instance MonadError PandocError PandocLua where catchError = Catch.catch throwError = Catch.throwM @@ -115,6 +79,22 @@ instance PandocMonad PandocLua where getCommonState = PandocLua $ do Lua.getglobal "PANDOC_STATE" forcePeek $ peekCommonState Lua.top - putCommonState = PandocLua . setGlobals . (:[]) . PANDOC_STATE + putCommonState cst = PandocLua $ do + pushCommonState cst + Lua.setglobal "PANDOC_STATE" logOutput = IO.logOutput + +-- | Retrieve a @'PandocError'@ from the Lua stack. +popPandocError :: LuaE PandocError PandocError +popPandocError = do + errResult <- runPeek $ peekPandocError top + case resultToEither errResult of + Right x -> return x + Left err -> return $ PandocLuaError (T.pack err) + +-- | Conversions between Lua errors and 'PandocError' exceptions. +instance LuaError PandocError where + popException = popPandocError + pushException = pushPandocError + luaException = PandocLuaError . T.pack |
