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/ErrorConversion.hs73
-rw-r--r--src/Text/Pandoc/Lua/Filter.hs252
-rw-r--r--src/Text/Pandoc/Lua/Global.hs52
-rw-r--r--src/Text/Pandoc/Lua/Init.hs134
-rw-r--r--src/Text/Pandoc/Lua/Marshal/CommonState.hs70
-rw-r--r--src/Text/Pandoc/Lua/Marshal/Context.hs (renamed from src/Text/Pandoc/Lua/Marshaling/Context.hs)6
-rw-r--r--src/Text/Pandoc/Lua/Marshal/PandocError.hs51
-rw-r--r--src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs133
-rw-r--r--src/Text/Pandoc/Lua/Marshal/Reference.hs107
-rw-r--r--src/Text/Pandoc/Lua/Marshal/Sources.hs46
-rw-r--r--src/Text/Pandoc/Lua/Marshaling.hs19
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/AST.hs378
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/AnyValue.hs24
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/CommonState.hs102
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/List.hs43
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/MediaBag.hs73
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/PandocError.hs65
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs79
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs59
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/Version.hs154
-rw-r--r--src/Text/Pandoc/Lua/Module/MediaBag.hs157
-rw-r--r--src/Text/Pandoc/Lua/Module/Pandoc.hs285
-rw-r--r--src/Text/Pandoc/Lua/Module/System.hs41
-rw-r--r--src/Text/Pandoc/Lua/Module/Types.hs84
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs293
-rw-r--r--src/Text/Pandoc/Lua/Orphans.hs116
-rw-r--r--src/Text/Pandoc/Lua/Packages.hs45
-rw-r--r--src/Text/Pandoc/Lua/PandocLua.hs62
-rw-r--r--src/Text/Pandoc/Lua/Util.hs117
-rw-r--r--src/Text/Pandoc/Lua/Walk.hs158
30 files changed, 1261 insertions, 2017 deletions
diff --git a/src/Text/Pandoc/Lua/ErrorConversion.hs b/src/Text/Pandoc/Lua/ErrorConversion.hs
index 4e6880722..5cb1bf825 100644
--- a/src/Text/Pandoc/Lua/ErrorConversion.hs
+++ b/src/Text/Pandoc/Lua/ErrorConversion.hs
@@ -1,6 +1,5 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE LambdaCase #-}
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Text.Pandoc.Lua.ErrorConversion
Copyright : © 2020-2021 Albert Krewinkel
@@ -13,49 +12,37 @@ Define how Lua errors are converted into @'PandocError'@ Haskell
exceptions, and /vice versa/.
-}
module Text.Pandoc.Lua.ErrorConversion
- ( errorConversion
+ ( addContextToException
) where
-import Foreign.Lua (Lua (..), NumResults)
+import HsLua (LuaError, LuaE, top)
+import HsLua.Marshalling (resultToEither, runPeek)
+import HsLua.Class.Peekable (PeekError (..))
import Text.Pandoc.Error (PandocError (PandocLuaError))
-import Text.Pandoc.Lua.Marshaling.PandocError (pushPandocError, peekPandocError)
+import Text.Pandoc.Lua.Marshal.PandocError (pushPandocError, peekPandocError)
-import qualified Control.Monad.Catch as Catch
import qualified Data.Text as T
-import qualified Foreign.Lua as Lua
-
--- | Conversions between Lua errors and Haskell exceptions, assuming
--- that all exceptions are of type @'PandocError'@.
-errorConversion :: Lua.ErrorConversion
-errorConversion = Lua.ErrorConversion
- { Lua.addContextToException = addContextToException
- , Lua.alternative = alternative
- , Lua.errorToException = errorToException
- , Lua.exceptionToError = exceptionToError
- }
-
--- | Convert a Lua error, which must be at the top of the stack, into a
--- @'PandocError'@, popping the value from the stack.
-errorToException :: forall a . Lua.State -> IO a
-errorToException l = Lua.unsafeRunWith l $ do
- err <- peekPandocError Lua.stackTop
- Lua.pop 1
- Catch.throwM err
-
--- | Try the first op -- if it doesn't succeed, run the second.
-alternative :: forall a . Lua a -> Lua a -> Lua a
-alternative x y = Catch.try x >>= \case
- Left (_ :: PandocError) -> y
- Right x' -> return x'
-
--- | Add more context to an error
-addContextToException :: forall a . String -> Lua a -> Lua a
-addContextToException ctx op = op `Catch.catch` \case
- PandocLuaError msg -> Catch.throwM $ PandocLuaError (T.pack ctx <> msg)
- e -> Catch.throwM e
-
--- | Catch a @'PandocError'@ exception and raise it as a Lua error.
-exceptionToError :: Lua NumResults -> Lua NumResults
-exceptionToError op = op `Catch.catch` \e -> do
- pushPandocError e
- Lua.error
+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
+
+instance PeekError PandocError where
+ messageFromException = \case
+ PandocLuaError m -> T.unpack m
+ err -> show err
diff --git a/src/Text/Pandoc/Lua/Filter.hs b/src/Text/Pandoc/Lua/Filter.hs
index 01bf90efa..9910424d8 100644
--- a/src/Text/Pandoc/Lua/Filter.hs
+++ b/src/Text/Pandoc/Lua/Filter.hs
@@ -1,4 +1,7 @@
-{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE IncoherentInstances #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Text.Pandoc.Lua.Filter
Copyright : © 2012-2021 John MacFarlane,
@@ -9,245 +12,36 @@ Stability : alpha
Types and functions for running Lua filters.
-}
-module Text.Pandoc.Lua.Filter ( LuaFilterFunction
- , LuaFilter
- , runFilterFile
- , walkInlines
- , walkInlineLists
- , walkBlocks
- , walkBlockLists
- , module Text.Pandoc.Lua.Walk
- ) where
-import Control.Applicative ((<|>))
-import Control.Monad (mplus, (>=>))
-import Control.Monad.Catch (finally, try)
-import Data.Data (Data, DataType, dataTypeConstrs, dataTypeName, dataTypeOf,
- showConstr, toConstr, tyconUQname)
-import Data.Foldable (foldrM)
-import Data.List (foldl')
-import Data.Map (Map)
-import Data.Maybe (fromMaybe)
-import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
+module Text.Pandoc.Lua.Filter
+ ( runFilterFile
+ ) where
+import Control.Monad ((>=>), (<$!>))
+import HsLua as Lua
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError)
-import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Marshaling.List (List (..))
-import Text.Pandoc.Lua.Walk (SingletonsList (..))
-import Text.Pandoc.Walk (Walkable (walkM))
+import Text.Pandoc.Lua.ErrorConversion ()
+import Text.Pandoc.Lua.Marshal.AST
+import Text.Pandoc.Lua.Marshal.Filter
-import qualified Data.Map.Strict as Map
-import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.Lua.Util as LuaUtil
-- | Transform document using the filter defined in the given file.
-runFilterFile :: FilePath -> Pandoc -> Lua Pandoc
+runFilterFile :: FilePath -> Pandoc -> LuaE PandocError Pandoc
runFilterFile filterPath doc = do
- top <- Lua.gettop
+ oldtop <- gettop
stat <- LuaUtil.dofileWithTraceback filterPath
if stat /= Lua.OK
- then Lua.throwTopMessage
+ then throwErrorAsException
else do
- newtop <- Lua.gettop
+ newtop <- gettop
-- Use the returned filters, or the implicitly defined global
-- filter if nothing was returned.
- luaFilters <- if newtop - top >= 1
- then Lua.peek Lua.stackTop
- else Lua.pushglobaltable *> fmap (:[]) Lua.popValue
+ luaFilters <- forcePeek $
+ if newtop - oldtop >= 1
+ then peekList peekFilter top
+ else (:[]) <$!> (liftLua pushglobaltable *> peekFilter top)
+ settop oldtop
runAll luaFilters doc
-runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
-runAll = foldr ((>=>) . walkMWithLuaFilter) return
-
--- | Filter function stored in the registry
-newtype LuaFilterFunction = LuaFilterFunction Lua.Reference
-
--- | Collection of filter functions (at most one function per element
--- constructor)
-newtype LuaFilter = LuaFilter (Map String LuaFilterFunction)
-
-instance Peekable LuaFilter where
- peek idx = do
- let constrs = listOfInlinesFilterName
- : listOfBlocksFilterName
- : metaFilterName
- : pandocFilterNames
- ++ blockElementNames
- ++ inlineElementNames
- let go constr acc = do
- Lua.getfield idx constr
- filterFn <- registerFilterFunction
- return $ case filterFn of
- Nothing -> acc
- Just fn -> Map.insert constr fn acc
- LuaFilter <$> foldrM go Map.empty constrs
-
--- | Register the function at the top of the stack as a filter function in the
--- registry.
-registerFilterFunction :: Lua (Maybe LuaFilterFunction)
-registerFilterFunction = do
- isFn <- Lua.isfunction Lua.stackTop
- if isFn
- then Just . LuaFilterFunction <$> Lua.ref Lua.registryindex
- else Nothing <$ Lua.pop 1
-
--- | Retrieve filter function from registry and push it to the top of the stack.
-pushFilterFunction :: LuaFilterFunction -> Lua ()
-pushFilterFunction (LuaFilterFunction fnRef) =
- Lua.getref Lua.registryindex fnRef
-
--- | Fetch either a list of elements from the stack. If there is a single
--- element instead of a list, fetch that element as a singleton list. If the top
--- of the stack is nil, return the default element that was passed to this
--- function. If none of these apply, raise an error.
-elementOrList :: Peekable a => a -> Lua [a]
-elementOrList x = do
- let topOfStack = Lua.stackTop
- elementUnchanged <- Lua.isnil topOfStack
- if elementUnchanged
- then [x] <$ Lua.pop 1
- else do
- mbres <- peekEither topOfStack
- case mbres of
- Right res -> [res] <$ Lua.pop 1
- Left _ -> Lua.peekList topOfStack `finally` Lua.pop 1
-
--- | Pop and return a value from the stack; if the value at the top of
--- the stack is @nil@, return the fallback element.
-popOption :: Peekable a => a -> Lua a
-popOption fallback = fromMaybe fallback . Lua.fromOptional <$> Lua.popValue
-
--- | Apply filter on a sequence of AST elements. Both lists and single
--- value are accepted as filter function return values.
-runOnSequence :: (Data a, Peekable a, Pushable a)
- => LuaFilter -> SingletonsList a -> Lua (SingletonsList a)
-runOnSequence (LuaFilter fnMap) (SingletonsList xs) =
- SingletonsList <$> mconcatMapM tryFilter xs
- where
- tryFilter :: (Data a, Peekable a, Pushable a) => a -> Lua [a]
- tryFilter x =
- let filterFnName = showConstr (toConstr x)
- catchAllName = tyconUQname $ dataTypeName (dataTypeOf x)
- in case Map.lookup filterFnName fnMap <|> Map.lookup catchAllName fnMap of
- Just fn -> runFilterFunction fn x *> elementOrList x
- Nothing -> return [x]
-
--- | Try filtering the given value without type error corrections on
--- the return value.
-runOnValue :: (Data a, Peekable a, Pushable a)
- => String -> LuaFilter -> a -> Lua a
-runOnValue filterFnName (LuaFilter fnMap) x =
- case Map.lookup filterFnName fnMap of
- Just fn -> runFilterFunction fn x *> popOption x
- Nothing -> return x
-
--- | Push a value to the stack via a lua filter function. The filter function is
--- called with given element as argument and is expected to return an element.
--- Alternatively, the function can return nothing or nil, in which case the
--- element is left unchanged.
-runFilterFunction :: Pushable a => LuaFilterFunction -> a -> Lua ()
-runFilterFunction lf x = do
- pushFilterFunction lf
- Lua.push x
- LuaUtil.callWithTraceback 1 1
-
-walkMWithLuaFilter :: LuaFilter -> Pandoc -> Lua Pandoc
-walkMWithLuaFilter f =
- walkInlines f
- >=> walkInlineLists f
- >=> walkBlocks f
- >=> walkBlockLists f
- >=> walkMeta f
- >=> walkPandoc f
-
-mconcatMapM :: (Monad m) => (a -> m [a]) -> [a] -> m [a]
-mconcatMapM f = fmap mconcat . mapM f
-
-hasOneOf :: LuaFilter -> [String] -> Bool
-hasOneOf (LuaFilter fnMap) = any (`Map.member` fnMap)
-
-contains :: LuaFilter -> String -> Bool
-contains (LuaFilter fnMap) = (`Map.member` fnMap)
-
-walkInlines :: Walkable (SingletonsList Inline) a => LuaFilter -> a -> Lua a
-walkInlines lf =
- let f :: SingletonsList Inline -> Lua (SingletonsList Inline)
- f = runOnSequence lf
- in if lf `hasOneOf` inlineElementNames
- then walkM f
- else return
-
-walkInlineLists :: Walkable (List Inline) a => LuaFilter -> a -> Lua a
-walkInlineLists lf =
- let f :: List Inline -> Lua (List Inline)
- f = runOnValue listOfInlinesFilterName lf
- in if lf `contains` listOfInlinesFilterName
- then walkM f
- else return
-
-walkBlocks :: Walkable (SingletonsList Block) a => LuaFilter -> a -> Lua a
-walkBlocks lf =
- let f :: SingletonsList Block -> Lua (SingletonsList Block)
- f = runOnSequence lf
- in if lf `hasOneOf` blockElementNames
- then walkM f
- else return
-
-walkBlockLists :: Walkable (List Block) a => LuaFilter -> a -> Lua a
-walkBlockLists lf =
- let f :: List Block -> Lua (List Block)
- f = runOnValue listOfBlocksFilterName lf
- in if lf `contains` listOfBlocksFilterName
- then walkM f
- else return
-
-walkMeta :: LuaFilter -> Pandoc -> Lua Pandoc
-walkMeta lf (Pandoc m bs) = do
- m' <- runOnValue "Meta" lf m
- return $ Pandoc m' bs
-
-walkPandoc :: LuaFilter -> Pandoc -> Lua Pandoc
-walkPandoc (LuaFilter fnMap) =
- case foldl' mplus Nothing (map (`Map.lookup` fnMap) pandocFilterNames) of
- Just fn -> \x -> runFilterFunction fn x *> singleElement x
- Nothing -> return
-
-constructorsFor :: DataType -> [String]
-constructorsFor x = map show (dataTypeConstrs x)
-
-inlineElementNames :: [String]
-inlineElementNames = "Inline" : constructorsFor (dataTypeOf (Str mempty))
-
-blockElementNames :: [String]
-blockElementNames = "Block" : constructorsFor (dataTypeOf (Para []))
-
-listOfInlinesFilterName :: String
-listOfInlinesFilterName = "Inlines"
-
-listOfBlocksFilterName :: String
-listOfBlocksFilterName = "Blocks"
-
-metaFilterName :: String
-metaFilterName = "Meta"
-
-pandocFilterNames :: [String]
-pandocFilterNames = ["Pandoc", "Doc"]
-
-singleElement :: Peekable a => a -> Lua a
-singleElement x = do
- elementUnchanged <- Lua.isnil (-1)
- if elementUnchanged
- then x <$ Lua.pop 1
- else do
- mbres <- peekEither (-1)
- case mbres of
- Right res -> res <$ Lua.pop 1
- Left err -> do
- Lua.pop 1
- Lua.throwMessage
- ("Error while trying to get a filter's return " <>
- "value from Lua stack.\n" <> show err)
-
--- | Try to convert the value at the given stack index to a Haskell value.
--- Returns @Left@ with an error message on failure.
-peekEither :: Peekable a => StackIndex -> Lua (Either PandocError a)
-peekEither = try . Lua.peek
+runAll :: [Filter] -> Pandoc -> LuaE PandocError Pandoc
+runAll = foldr ((>=>) . applyFully) return
diff --git a/src/Text/Pandoc/Lua/Global.hs b/src/Text/Pandoc/Lua/Global.hs
index 29b788f04..cf82890c6 100644
--- a/src/Text/Pandoc/Lua/Global.hs
+++ b/src/Text/Pandoc/Lua/Global.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua
Copyright : Copyright © 2017-2021 Albert Krewinkel
@@ -14,19 +14,19 @@ module Text.Pandoc.Lua.Global
, setGlobals
) where
-import Data.Data (Data)
-import Foreign.Lua (Lua, Peekable, Pushable)
-import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable
- , metatableName)
+import HsLua as Lua
+import HsLua.Module.Version (pushVersion)
import Paths_pandoc (version)
import Text.Pandoc.Class.CommonState (CommonState)
-import Text.Pandoc.Definition (Pandoc (Pandoc), pandocTypesVersion)
-import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Util (addFunction)
+import Text.Pandoc.Definition (Pandoc, pandocTypesVersion)
+import Text.Pandoc.Error (PandocError)
+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.Orphans ()
import Text.Pandoc.Options (ReaderOptions)
import qualified Data.Text as Text
-import qualified Foreign.Lua as Lua
-- | Permissible global Lua variables.
data Global =
@@ -40,50 +40,30 @@ data Global =
-- Cannot derive instance of Data because of CommonState
-- | Set all given globals.
-setGlobals :: [Global] -> Lua ()
+setGlobals :: [Global] -> LuaE PandocError ()
setGlobals = mapM_ setGlobal
-setGlobal :: Global -> Lua ()
+setGlobal :: Global -> LuaE PandocError ()
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 pandocTypesVersion
+ pushVersion pandocTypesVersion
Lua.setglobal "PANDOC_API_VERSION"
PANDOC_DOCUMENT doc -> do
- Lua.push (LazyPandoc doc)
+ pushPandoc doc
Lua.setglobal "PANDOC_DOCUMENT"
PANDOC_READER_OPTIONS ropts -> do
- Lua.push ropts
+ pushReaderOptionsReadonly 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
+ pushCommonState commonState
Lua.setglobal "PANDOC_STATE"
PANDOC_VERSION -> do
- Lua.push version
+ pushVersion 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 baa6f0295..835da1fc9 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua
Copyright : Copyright © 2017-2021 Albert Krewinkel
@@ -12,25 +14,24 @@ module Text.Pandoc.Lua.Init
( runLua
) where
-import Control.Monad (when)
-import Control.Monad.Catch (try)
+import Control.Monad (forM, forM_, when)
+import Control.Monad.Catch (throwM, try)
import Control.Monad.Trans (MonadIO (..))
-import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
-import Foreign.Lua (Lua)
+import Data.Maybe (catMaybes)
+import HsLua as Lua hiding (status, try)
import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
-import Text.Pandoc.Class.PandocMonad (readDataFile)
-import Text.Pandoc.Class.PandocIO (PandocIO)
-import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Class.PandocMonad (PandocMonad, readDataFile)
+import Text.Pandoc.Error (PandocError (PandocLuaError))
import Text.Pandoc.Lua.Packages (installPandocPackageSearcher)
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, runPandocLua)
-import Text.Pandoc.Lua.Util (throwTopMessageAsError')
-import qualified Foreign.Lua as Lua
-import qualified Text.Pandoc.Definition as Pandoc
+import qualified Data.Text as T
+import qualified Lua.LPeg as LPeg
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)
+ => LuaE PandocError a -> m (Either PandocError a)
runLua luaOp = do
enc <- liftIO $ getForeignEncoding <* setForeignEncoding utf8
res <- runPandocLua . try $ do
@@ -39,12 +40,27 @@ runLua luaOp = do
liftIO $ setForeignEncoding enc
return res
+-- | Modules that are loaded at startup and assigned to fields in the
+-- pandoc module.
+loadedModules :: [(Name, Name)]
+loadedModules =
+ [ ("pandoc.List", "List")
+ , ("pandoc.mediabag", "mediabag")
+ , ("pandoc.path", "path")
+ , ("pandoc.system", "system")
+ , ("pandoc.types", "types")
+ , ("pandoc.utils", "utils")
+ , ("text", "text")
+ ]
+
-- | Initialize the lua state with all required values
initLuaState :: PandocLua ()
initLuaState = do
liftPandocLua Lua.openlibs
installPandocPackageSearcher
initPandocModule
+ installLpegSearcher
+ setGlobalModules
loadInitScript "init.lua"
where
initPandocModule :: PandocLua ()
@@ -53,12 +69,16 @@ initLuaState = do
ModulePandoc.pushModule
-- register as loaded module
liftPandocLua $ do
- Lua.pushvalue Lua.stackTop
- Lua.getfield Lua.registryindex Lua.loadedTableRegistryField
- Lua.setfield (Lua.nthFromTop 2) "pandoc"
- Lua.pop 1
- -- copy constructors into registry
- putConstructorsInRegistry
+ Lua.getfield Lua.registryindex Lua.loaded
+ Lua.pushvalue (Lua.nth 2)
+ Lua.setfield (Lua.nth 2) "pandoc"
+ Lua.pop 1 -- remove LOADED table
+ -- load modules and add them to the `pandoc` module table.
+ liftPandocLua $ forM_ loadedModules $ \(pkgname, fieldname) -> do
+ Lua.getglobal "require"
+ Lua.pushName pkgname
+ Lua.call 1 1
+ Lua.setfield (nth 2) fieldname
-- assign module to global variable
liftPandocLua $ Lua.setglobal "pandoc"
@@ -66,38 +86,54 @@ initLuaState = do
loadInitScript scriptFile = do
script <- readDataFile scriptFile
status <- liftPandocLua $ Lua.dostring script
- when (status /= Lua.OK) . liftPandocLua $
- throwTopMessageAsError'
- (("Couldn't load '" ++ scriptFile ++ "'.\n") ++)
+ when (status /= Lua.OK) . liftPandocLua $ do
+ err <- popException
+ let prefix = "Couldn't load '" <> T.pack scriptFile <> "':\n"
+ throwM . PandocLuaError . (prefix <>) $ case err of
+ PandocLuaError msg -> msg
+ _ -> T.pack $ show err
+ setGlobalModules :: PandocLua ()
+ setGlobalModules = liftPandocLua $ do
+ let globalModules =
+ [ ("lpeg", LPeg.luaopen_lpeg_ptr) -- must be loaded first
+ , ("re", LPeg.luaopen_re_ptr) -- re depends on lpeg
+ ]
+ loadedBuiltInModules <- fmap catMaybes . forM globalModules $
+ \(pkgname, luaopen) -> do
+ Lua.pushcfunction luaopen
+ usedBuiltIn <- Lua.pcall 0 1 Nothing >>= \case
+ OK -> do -- all good, loading succeeded
+ -- register as loaded module so later modules can rely on this
+ Lua.getfield Lua.registryindex Lua.loaded
+ Lua.pushvalue (Lua.nth 2)
+ Lua.setfield (Lua.nth 2) pkgname
+ Lua.pop 1 -- pop _LOADED
+ return True
+ _ -> do -- built-in library failed, load system lib
+ Lua.pop 1 -- ignore error message
+ -- Try loading via the normal package loading mechanism.
+ Lua.getglobal "require"
+ Lua.pushName pkgname
+ Lua.call 1 1 -- Throws an exception if loading failed again!
+ return False
--- | AST elements are marshaled via normal constructor functions in the
--- @pandoc@ module. However, accessing Lua globals from Haskell is
--- expensive (due to error handling). Accessing the Lua registry is much
--- cheaper, which is why the constructor functions are copied into the
--- Lua registry and called from there.
---
--- This function expects the @pandoc@ module to be at the top of the
--- stack.
-putConstructorsInRegistry :: PandocLua ()
-putConstructorsInRegistry = liftPandocLua $ do
- constrsToReg $ Pandoc.Pandoc mempty mempty
- constrsToReg $ Pandoc.Str mempty
- constrsToReg $ Pandoc.Para mempty
- constrsToReg $ Pandoc.Meta mempty
- constrsToReg $ Pandoc.MetaList mempty
- constrsToReg $ Pandoc.Citation mempty mempty mempty Pandoc.AuthorInText 0 0
- putInReg "Attr" -- used for Attr type alias
- putInReg "ListAttributes" -- used for ListAttributes type alias
- putInReg "List" -- pandoc.List
- putInReg "SimpleTable" -- helper for backward-compatible table handling
- where
- constrsToReg :: Data a => a -> Lua ()
- constrsToReg = mapM_ (putInReg . showConstr) . dataTypeConstrs . dataTypeOf
+ -- Module on top of stack. Register as global
+ Lua.setglobal pkgname
+ return $ if usedBuiltIn then Just pkgname else Nothing
+
+ -- Remove module entry from _LOADED table in registry if we used a
+ -- built-in library. This ensures that later calls to @require@ will
+ -- prefer the shared library, if any.
+ forM_ loadedBuiltInModules $ \pkgname -> do
+ Lua.getfield Lua.registryindex Lua.loaded
+ Lua.pushnil
+ Lua.setfield (Lua.nth 2) pkgname
+ Lua.pop 1 -- registry
- putInReg :: String -> Lua ()
- putInReg name = do
- Lua.push ("pandoc." ++ name) -- name in registry
- Lua.push name -- in pandoc module
- Lua.rawget (Lua.nthFromTop 3)
- Lua.rawset Lua.registryindex
+ installLpegSearcher :: PandocLua ()
+ installLpegSearcher = liftPandocLua $ do
+ Lua.getglobal' "package.searchers"
+ Lua.pushHaskellFunction $ Lua.state >>= liftIO . LPeg.lpeg_searcher
+ Lua.rawseti (Lua.nth 2) . (+1) . fromIntegral =<< Lua.rawlen (Lua.nth 2)
+ Lua.pop 1 -- remove 'package.searchers' from stack
diff --git a/src/Text/Pandoc/Lua/Marshal/CommonState.hs b/src/Text/Pandoc/Lua/Marshal/CommonState.hs
new file mode 100644
index 000000000..a8c0e28d2
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/CommonState.hs
@@ -0,0 +1,70 @@
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshal.CommonState
+ Copyright : © 2012-2021 John MacFarlane
+ © 2017-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Instances to marshal (push) and unmarshal (peek) the common state.
+-}
+module Text.Pandoc.Lua.Marshal.CommonState
+ ( typeCommonState
+ , peekCommonState
+ , pushCommonState
+ ) where
+
+import HsLua.Core
+import HsLua.Marshalling
+import HsLua.Packaging
+import Text.Pandoc.Class (CommonState (..))
+import Text.Pandoc.Logging (LogMessage, showLogMessage)
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+
+-- | Lua type used for the @CommonState@ object.
+typeCommonState :: LuaError e => DocumentedType e CommonState
+typeCommonState = deftype "pandoc CommonState" []
+ [ readonly "input_files" "input files passed to pandoc"
+ (pushPandocList pushString, stInputFiles)
+
+ , readonly "output_file" "the file to which pandoc will write"
+ (maybe pushnil pushString, stOutputFile)
+
+ , readonly "log" "list of log messages"
+ (pushPandocList (pushUD typeLogMessage), stLog)
+
+ , readonly "request_headers" "headers to add for HTTP requests"
+ (pushPandocList (pushPair pushText pushText), stRequestHeaders)
+
+ , readonly "resource_path"
+ "path to search for resources like included images"
+ (pushPandocList pushString, stResourcePath)
+
+ , readonly "source_url" "absolute URL + dir of 1st source file"
+ (maybe pushnil pushText, stSourceURL)
+
+ , readonly "user_data_dir" "directory to search for data files"
+ (maybe pushnil pushString, stUserDataDir)
+
+ , readonly "trace" "controls whether tracing messages are issued"
+ (pushBool, stTrace)
+
+ , readonly "verbosity" "verbosity level"
+ (pushString . show, stVerbosity)
+ ]
+
+peekCommonState :: LuaError e => Peeker e CommonState
+peekCommonState = peekUD typeCommonState
+
+pushCommonState :: LuaError e => Pusher e CommonState
+pushCommonState = pushUD typeCommonState
+
+typeLogMessage :: LuaError e => DocumentedType e LogMessage
+typeLogMessage = deftype "pandoc LogMessage"
+ [ operation Index $ defun "__tostring"
+ ### liftPure showLogMessage
+ <#> udparam typeLogMessage "msg" "object"
+ =#> functionResult pushText "string" "stringified log message"
+ ]
+ mempty -- no members
diff --git a/src/Text/Pandoc/Lua/Marshaling/Context.hs b/src/Text/Pandoc/Lua/Marshal/Context.hs
index 606bdcfb2..17af936e1 100644
--- a/src/Text/Pandoc/Lua/Marshaling/Context.hs
+++ b/src/Text/Pandoc/Lua/Marshal/Context.hs
@@ -10,10 +10,10 @@
Marshaling instance for doctemplates Context and its components.
-}
-module Text.Pandoc.Lua.Marshaling.Context () where
+module Text.Pandoc.Lua.Marshal.Context () where
-import qualified Foreign.Lua as Lua
-import Foreign.Lua (Pushable)
+import qualified HsLua as Lua
+import HsLua (Pushable)
import Text.DocTemplates (Context(..), Val(..), TemplateTarget)
import Text.DocLayout (render)
diff --git a/src/Text/Pandoc/Lua/Marshal/PandocError.hs b/src/Text/Pandoc/Lua/Marshal/PandocError.hs
new file mode 100644
index 000000000..d1c0ad4f4
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/PandocError.hs
@@ -0,0 +1,51 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshal.PandocError
+ Copyright : © 2020-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Marshal of @'PandocError'@ values.
+-}
+module Text.Pandoc.Lua.Marshal.PandocError
+ ( peekPandocError
+ , pushPandocError
+ , typePandocError
+ )
+ where
+
+import HsLua.Core (LuaError)
+import HsLua.Marshalling (Peeker, Pusher, pushString, liftLua)
+import HsLua.Packaging
+import Text.Pandoc.Error (PandocError (PandocLuaError))
+
+import qualified HsLua as Lua
+import qualified Text.Pandoc.UTF8 as UTF8
+
+-- | Lua userdata type definition for PandocError.
+typePandocError :: LuaError e => DocumentedType e PandocError
+typePandocError = deftype "PandocError"
+ [ operation Tostring $ defun "__tostring"
+ ### liftPure (show @PandocError)
+ <#> udparam typePandocError "obj" "PandocError object"
+ =#> functionResult pushString "string" "string representation of error."
+ ]
+ mempty -- no members
+
+-- | Peek a @'PandocError'@ element to the Lua stack.
+pushPandocError :: LuaError e => Pusher e PandocError
+pushPandocError = pushUD typePandocError
+
+-- | Retrieve a @'PandocError'@ from the Lua stack.
+peekPandocError :: LuaError e => Peeker e PandocError
+peekPandocError idx = Lua.retrieving "PandocError" $
+ liftLua (Lua.ltype idx) >>= \case
+ Lua.TypeUserdata -> peekUD typePandocError idx
+ _ -> do
+ msg <- liftLua $ Lua.state >>= \l -> Lua.liftIO (Lua.popErrorMessage l)
+ return $ PandocLuaError (UTF8.toText msg)
diff --git a/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs b/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs
new file mode 100644
index 000000000..c20770dba
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs
@@ -0,0 +1,133 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshaling.ReaderOptions
+ Copyright : © 2012-2021 John MacFarlane
+ © 2017-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Marshaling instance for ReaderOptions and its components.
+-}
+module Text.Pandoc.Lua.Marshal.ReaderOptions
+ ( peekReaderOptions
+ , pushReaderOptions
+ , pushReaderOptionsReadonly
+ ) where
+
+import Data.Default (def)
+import HsLua as Lua
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+import Text.Pandoc.Options (ReaderOptions (..))
+
+--
+-- Reader Options
+--
+
+-- | Retrieve a ReaderOptions value, either from a normal ReaderOptions
+-- value, from a read-only object, or from a table with the same
+-- keys as a ReaderOptions object.
+peekReaderOptions :: LuaError e => Peeker e ReaderOptions
+peekReaderOptions = retrieving "ReaderOptions" . \idx ->
+ liftLua (ltype idx) >>= \case
+ TypeUserdata -> choice [ peekUD typeReaderOptions
+ , peekUD typeReaderOptionsReadonly
+ ]
+ idx
+ TypeTable -> peekReaderOptionsTable idx
+ _ -> failPeek =<<
+ typeMismatchMessage "ReaderOptions userdata or table" idx
+
+-- | Pushes a ReaderOptions value as userdata object.
+pushReaderOptions :: LuaError e => Pusher e ReaderOptions
+pushReaderOptions = pushUD typeReaderOptions
+
+-- | Pushes a ReaderOptions object, but makes it read-only.
+pushReaderOptionsReadonly :: LuaError e => Pusher e ReaderOptions
+pushReaderOptionsReadonly = pushUD typeReaderOptionsReadonly
+
+-- | ReaderOptions object type for read-only values.
+typeReaderOptionsReadonly :: LuaError e => DocumentedType e ReaderOptions
+typeReaderOptionsReadonly = deftype "ReaderOptions (read-only)"
+ [ operation Tostring $ lambda
+ ### liftPure show
+ <#> udparam typeReaderOptions "opts" "options to print in native format"
+ =#> functionResult pushString "string" "Haskell representation"
+ , operation Newindex $ lambda
+ ### (failLua "This ReaderOptions value is read-only.")
+ =?> "Throws an error when called, i.e., an assignment is made."
+ ]
+ readerOptionsMembers
+
+-- | 'ReaderOptions' object type.
+typeReaderOptions :: LuaError e => DocumentedType e ReaderOptions
+typeReaderOptions = deftype "ReaderOptions"
+ [ operation Tostring $ lambda
+ ### liftPure show
+ <#> udparam typeReaderOptions "opts" "options to print in native format"
+ =#> functionResult pushString "string" "Haskell representation"
+ ]
+ readerOptionsMembers
+
+-- | Member properties of 'ReaderOptions' Lua values.
+readerOptionsMembers :: LuaError e
+ => [Member e (DocumentedFunction e) ReaderOptions]
+readerOptionsMembers =
+ [ property "abbreviations" ""
+ (pushSet pushText, readerAbbreviations)
+ (peekSet peekText, \opts x -> opts{ readerAbbreviations = x })
+ , property "columns" ""
+ (pushIntegral, readerColumns)
+ (peekIntegral, \opts x -> opts{ readerColumns = x })
+ , property "default_image_extension" ""
+ (pushText, readerDefaultImageExtension)
+ (peekText, \opts x -> opts{ readerDefaultImageExtension = x })
+ , property "extensions" ""
+ (pushString . show, readerExtensions)
+ (peekRead, \opts x -> opts{ readerExtensions = x })
+ , property "indented_code_classes" ""
+ (pushPandocList pushText, readerIndentedCodeClasses)
+ (peekList peekText, \opts x -> opts{ readerIndentedCodeClasses = x })
+ , property "strip_comments" ""
+ (pushBool, readerStripComments)
+ (peekBool, \opts x -> opts{ readerStripComments = x })
+ , property "standalone" ""
+ (pushBool, readerStandalone)
+ (peekBool, \opts x -> opts{ readerStandalone = x })
+ , property "tab_stop" ""
+ (pushIntegral, readerTabStop)
+ (peekIntegral, \opts x -> opts{ readerTabStop = x })
+ , property "track_changes" ""
+ (pushString . show, readerTrackChanges)
+ (peekRead, \opts x -> opts{ readerTrackChanges = x })
+ ]
+
+-- | Retrieves a 'ReaderOptions' object from a table on the stack, using
+-- the default values for all missing fields.
+--
+-- Internally, this pushes the default reader options, sets each
+-- key/value pair of the table in the userdata value, then retrieves the
+-- object again. This will update all fields and complain about unknown
+-- keys.
+peekReaderOptionsTable :: LuaError e => Peeker e ReaderOptions
+peekReaderOptionsTable idx = retrieving "ReaderOptions (table)" $ do
+ liftLua $ do
+ absidx <- absindex idx
+ pushUD typeReaderOptions def
+ let setFields = do
+ next absidx >>= \case
+ False -> return () -- all fields were copied
+ True -> do
+ pushvalue (nth 2) *> insert (nth 2)
+ settable (nth 4) -- set in userdata object
+ setFields
+ pushnil -- first key
+ setFields
+ peekUD typeReaderOptions top
+
+instance Pushable ReaderOptions where
+ push = pushReaderOptions
diff --git a/src/Text/Pandoc/Lua/Marshal/Reference.hs b/src/Text/Pandoc/Lua/Marshal/Reference.hs
new file mode 100644
index 000000000..ee297484e
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/Reference.hs
@@ -0,0 +1,107 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshaling.ReaderOptions
+ Copyright : © 2012-2021 John MacFarlane
+ © 2017-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Marshal citeproc 'Reference' values.
+-}
+module Text.Pandoc.Lua.Marshal.Reference
+ ( pushReference
+ ) where
+
+import Citeproc.Types
+ ( Date (..), DateParts (..), ItemId (..), Name (..), Reference (..)
+ , Val (..), Variable, fromVariable
+ )
+import Control.Monad (forM_)
+import HsLua hiding (Name, Reference, pushName, peekName)
+import Text.Pandoc.Builder (Inlines, toList)
+import Text.Pandoc.Lua.Marshal.Inline (pushInlines)
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+
+import qualified Data.Map as Map
+import qualified HsLua
+
+-- | Pushes a ReaderOptions value as userdata object.
+pushReference :: LuaError e => Pusher e (Reference Inlines)
+pushReference reference = do
+ pushAsTable [ ("id", pushItemId . referenceId)
+ , ("type", pushText . referenceType)
+ ]
+ reference
+ forM_ (Map.toList $ referenceVariables reference) $ \(var, val) -> do
+ pushVariable var
+ pushVal val
+ rawset (nth 3)
+
+-- | Pushes an 'ItemId' as a string.
+pushItemId :: Pusher e ItemId
+pushItemId = pushText . unItemId
+
+-- | Pushes a person's 'Name' as a table.
+pushName :: LuaError e => Pusher e Name
+pushName = pushAsTable
+ [ ("family" , pushTextOrNil . nameFamily)
+ , ("given" , pushTextOrNil . nameGiven)
+ , ("dropping-particle" , pushTextOrNil . nameDroppingParticle)
+ , ("non-dropping-particle" , pushTextOrNil . nameNonDroppingParticle)
+ , ("suffix" , pushTextOrNil . nameSuffix)
+ , ("literal" , pushTextOrNil . nameLiteral)
+ , ("comma-suffix" , pushBoolOrNil . nameCommaSuffix)
+ , ("static-ordering" , pushBoolOrNil . nameStaticOrdering)
+ ]
+ where
+ pushTextOrNil = \case
+ Nothing -> pushnil
+ Just xs -> pushText xs
+
+-- | Pushes a boolean, but uses @nil@ instead of @false@; table fields
+-- are not set unless the value is true.
+pushBoolOrNil :: Pusher e Bool
+pushBoolOrNil = \case
+ False -> pushnil
+ True -> pushBool True
+
+-- | Pushes a 'Variable' as string.
+pushVariable :: Pusher e Variable
+pushVariable = pushText . fromVariable
+
+-- | Pushes a 'Val', i.e., a variable value.
+pushVal :: LuaError e => Pusher e (Val Inlines)
+pushVal = \case
+ TextVal t -> pushText t
+ FancyVal inlns -> pushInlines $ toList inlns
+ NumVal i -> pushIntegral i
+ NamesVal names -> pushPandocList pushName names
+ DateVal date -> pushDate date
+
+-- | Pushes a 'Date' as table.
+pushDate :: LuaError e => Pusher e Date
+pushDate = pushAsTable
+ [ ("date-parts", pushPandocList pushDateParts . dateParts)
+ , ("circa", pushBoolOrNil . dateCirca)
+ , ("season", maybe pushnil pushIntegral . dateSeason)
+ , ("literal", maybe pushnil pushText . dateLiteral)
+ ]
+ where
+ -- date parts are lists of Int values
+ pushDateParts (DateParts dp) = pushPandocList pushIntegral dp
+
+-- | Helper funtion to push an object as a table.
+pushAsTable :: LuaError e
+ => [(HsLua.Name, a -> LuaE e ())]
+ -> a -> LuaE e ()
+pushAsTable props obj = do
+ createtable 0 (length props)
+ forM_ props $ \(name, pushValue) -> do
+ HsLua.pushName name
+ pushValue obj
+ rawset (nth 3)
diff --git a/src/Text/Pandoc/Lua/Marshal/Sources.hs b/src/Text/Pandoc/Lua/Marshal/Sources.hs
new file mode 100644
index 000000000..7b5262ab5
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/Sources.hs
@@ -0,0 +1,46 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+Module : Text.Pandoc.Lua.Marshaling.Sources
+Copyright : © 2021 Albert Krewinkel
+License : GNU GPL, version 2 or above
+Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+
+Marshal 'Sources'.
+-}
+module Text.Pandoc.Lua.Marshal.Sources
+ ( pushSources
+ ) where
+
+import Data.Text (Text)
+import HsLua as Lua
+import Text.Pandoc.Lua.Marshal.List (newListMetatable)
+import Text.Pandoc.Sources (Sources (..))
+import Text.Parsec (SourcePos, sourceName)
+
+-- | Pushes the 'Sources' as a list of lazy Lua objects.
+pushSources :: LuaError e => Pusher e Sources
+pushSources (Sources srcs) = do
+ pushList (pushUD typeSource) srcs
+ newListMetatable "pandoc Sources" $ do
+ pushName "__tostring"
+ pushHaskellFunction $ do
+ sources <- forcePeek $ peekList (peekUD typeSource) (nthBottom 1)
+ pushText . mconcat $ map snd sources
+ return 1
+ rawset (nth 3)
+ setmetatable (nth 2)
+
+-- | Source object type.
+typeSource :: LuaError e => DocumentedType e (SourcePos, Text)
+typeSource = deftype "pandoc input source"
+ [ operation Tostring $ lambda
+ ### liftPure snd
+ <#> udparam typeSource "srcs" "Source to print in native format"
+ =#> functionResult pushText "string" "Haskell representation"
+ ]
+ [ readonly "name" "source name"
+ (pushString, sourceName . fst)
+ , readonly "text" "source text"
+ (pushText, snd)
+ ]
diff --git a/src/Text/Pandoc/Lua/Marshaling.hs b/src/Text/Pandoc/Lua/Marshaling.hs
deleted file mode 100644
index f517c7c27..000000000
--- a/src/Text/Pandoc/Lua/Marshaling.hs
+++ /dev/null
@@ -1,19 +0,0 @@
-{- |
- Module : Text.Pandoc.Lua.Marshaling
- Copyright : © 2012-2021 John MacFarlane
- © 2017-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
-
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Lua marshaling (pushing) and unmarshaling (peeking) instances.
--}
-module Text.Pandoc.Lua.Marshaling () where
-
-import Text.Pandoc.Lua.Marshaling.AST ()
-import Text.Pandoc.Lua.Marshaling.CommonState ()
-import Text.Pandoc.Lua.Marshaling.Context ()
-import Text.Pandoc.Lua.Marshaling.PandocError()
-import Text.Pandoc.Lua.Marshaling.ReaderOptions ()
-import Text.Pandoc.Lua.Marshaling.Version ()
diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs
deleted file mode 100644
index 8e12d232c..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/AST.hs
+++ /dev/null
@@ -1,378 +0,0 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-{-# LANGUAGE BangPatterns #-}
-{-# LANGUAGE LambdaCase #-}
-{- |
- Module : Text.Pandoc.Lua.Marshaling.AST
- Copyright : © 2012-2021 John MacFarlane
- © 2017-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
-
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Marshaling/unmarshaling instances for document AST elements.
--}
-module Text.Pandoc.Lua.Marshaling.AST
- ( LuaAttr (..)
- , LuaListAttributes (..)
- ) where
-
-import Control.Applicative ((<|>))
-import Control.Monad ((<$!>))
-import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
-import Text.Pandoc.Definition
-import Text.Pandoc.Error (PandocError)
-import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor)
-import Text.Pandoc.Lua.Marshaling.CommonState ()
-
-import qualified Control.Monad.Catch as Catch
-import qualified Foreign.Lua as Lua
-import qualified Text.Pandoc.Lua.Util as LuaUtil
-
-instance Pushable Pandoc where
- push (Pandoc meta blocks) =
- pushViaConstructor "Pandoc" blocks meta
-
-instance Peekable Pandoc where
- peek idx = defineHowTo "get Pandoc value" $! Pandoc
- <$!> LuaUtil.rawField idx "meta"
- <*> LuaUtil.rawField idx "blocks"
-
-instance Pushable Meta where
- push (Meta mmap) =
- pushViaConstructor "Meta" mmap
-instance Peekable Meta where
- peek idx = defineHowTo "get Meta value" $!
- Meta <$!> Lua.peek idx
-
-instance Pushable MetaValue where
- push = pushMetaValue
-instance Peekable MetaValue where
- peek = peekMetaValue
-
-instance Pushable Block where
- push = pushBlock
-
-instance Peekable Block where
- peek = peekBlock
-
--- Inline
-instance Pushable Inline where
- push = pushInline
-
-instance Peekable Inline where
- peek = peekInline
-
--- Citation
-instance Pushable Citation where
- push (Citation cid prefix suffix mode noteNum hash) =
- pushViaConstructor "Citation" cid mode prefix suffix noteNum hash
-
-instance Peekable Citation where
- peek idx = Citation
- <$!> LuaUtil.rawField idx "id"
- <*> LuaUtil.rawField idx "prefix"
- <*> LuaUtil.rawField idx "suffix"
- <*> LuaUtil.rawField idx "mode"
- <*> LuaUtil.rawField idx "note_num"
- <*> LuaUtil.rawField idx "hash"
-
-instance Pushable Alignment where
- push = Lua.push . show
-instance Peekable Alignment where
- peek = Lua.peekRead
-
-instance Pushable CitationMode where
- push = Lua.push . show
-instance Peekable CitationMode where
- peek = Lua.peekRead
-
-instance Pushable Format where
- push (Format f) = Lua.push f
-instance Peekable Format where
- peek idx = Format <$!> Lua.peek idx
-
-instance Pushable ListNumberDelim where
- push = Lua.push . show
-instance Peekable ListNumberDelim where
- peek = Lua.peekRead
-
-instance Pushable ListNumberStyle where
- push = Lua.push . show
-instance Peekable ListNumberStyle where
- peek = Lua.peekRead
-
-instance Pushable MathType where
- push = Lua.push . show
-instance Peekable MathType where
- peek = Lua.peekRead
-
-instance Pushable QuoteType where
- push = Lua.push . show
-instance Peekable QuoteType where
- peek = Lua.peekRead
-
--- | Push an meta value element to the top of the lua stack.
-pushMetaValue :: MetaValue -> Lua ()
-pushMetaValue = \case
- MetaBlocks blcks -> pushViaConstructor "MetaBlocks" blcks
- MetaBool bool -> Lua.push bool
- MetaInlines inlns -> pushViaConstructor "MetaInlines" inlns
- MetaList metalist -> pushViaConstructor "MetaList" metalist
- MetaMap metamap -> pushViaConstructor "MetaMap" metamap
- MetaString str -> Lua.push str
-
--- | Interpret the value at the given stack index as meta value.
-peekMetaValue :: StackIndex -> Lua MetaValue
-peekMetaValue idx = defineHowTo "get MetaValue" $ do
- -- Get the contents of an AST element.
- let elementContent :: Peekable a => Lua a
- elementContent = Lua.peek idx
- luatype <- Lua.ltype idx
- case luatype of
- Lua.TypeBoolean -> MetaBool <$!> Lua.peek idx
- Lua.TypeString -> MetaString <$!> Lua.peek idx
- Lua.TypeTable -> do
- tag <- try $ LuaUtil.getTag idx
- case tag of
- Right "MetaBlocks" -> MetaBlocks <$!> elementContent
- Right "MetaBool" -> MetaBool <$!> elementContent
- Right "MetaMap" -> MetaMap <$!> elementContent
- Right "MetaInlines" -> MetaInlines <$!> elementContent
- Right "MetaList" -> MetaList <$!> elementContent
- Right "MetaString" -> MetaString <$!> elementContent
- Right t -> Lua.throwMessage ("Unknown meta tag: " <> t)
- Left _ -> do
- -- no meta value tag given, try to guess.
- len <- Lua.rawlen idx
- if len <= 0
- then MetaMap <$!> Lua.peek idx
- else (MetaInlines <$!> Lua.peek idx)
- <|> (MetaBlocks <$!> Lua.peek idx)
- <|> (MetaList <$!> Lua.peek idx)
- _ -> Lua.throwMessage "could not get meta value"
-
--- | Push a block element to the top of the Lua stack.
-pushBlock :: Block -> Lua ()
-pushBlock = \case
- BlockQuote blcks -> pushViaConstructor "BlockQuote" blcks
- BulletList items -> pushViaConstructor "BulletList" items
- CodeBlock attr code -> pushViaConstructor "CodeBlock" code (LuaAttr attr)
- DefinitionList items -> pushViaConstructor "DefinitionList" items
- Div attr blcks -> pushViaConstructor "Div" blcks (LuaAttr attr)
- Header lvl attr inlns -> pushViaConstructor "Header" lvl inlns (LuaAttr attr)
- HorizontalRule -> pushViaConstructor "HorizontalRule"
- LineBlock blcks -> pushViaConstructor "LineBlock" blcks
- OrderedList lstAttr list -> pushViaConstructor "OrderedList" list
- (LuaListAttributes lstAttr)
- Null -> pushViaConstructor "Null"
- Para blcks -> pushViaConstructor "Para" blcks
- Plain blcks -> pushViaConstructor "Plain" blcks
- RawBlock f cs -> pushViaConstructor "RawBlock" f cs
- Table attr blkCapt specs thead tbody tfoot ->
- pushViaConstructor "Table" blkCapt specs thead tbody tfoot attr
-
--- | Return the value at the given index as block if possible.
-peekBlock :: StackIndex -> Lua Block
-peekBlock idx = defineHowTo "get Block value" $! do
- tag <- LuaUtil.getTag idx
- case tag of
- "BlockQuote" -> BlockQuote <$!> elementContent
- "BulletList" -> BulletList <$!> elementContent
- "CodeBlock" -> withAttr CodeBlock <$!> elementContent
- "DefinitionList" -> DefinitionList <$!> elementContent
- "Div" -> withAttr Div <$!> elementContent
- "Header" -> (\(lvl, LuaAttr attr, lst) -> Header lvl attr lst)
- <$!> elementContent
- "HorizontalRule" -> return HorizontalRule
- "LineBlock" -> LineBlock <$!> elementContent
- "OrderedList" -> (\(LuaListAttributes lstAttr, lst) ->
- OrderedList lstAttr lst)
- <$!> elementContent
- "Null" -> return Null
- "Para" -> Para <$!> elementContent
- "Plain" -> Plain <$!> elementContent
- "RawBlock" -> uncurry RawBlock <$!> elementContent
- "Table" -> (\(attr, capt, colSpecs, thead, tbodies, tfoot) ->
- Table (fromLuaAttr attr)
- capt
- colSpecs
- thead
- tbodies
- tfoot)
- <$!> elementContent
- _ -> Lua.throwMessage ("Unknown block type: " <> tag)
- where
- -- Get the contents of an AST element.
- elementContent :: Peekable a => Lua a
- elementContent = LuaUtil.rawField idx "c"
-
-instance Pushable Caption where
- push = pushCaption
-
-instance Peekable Caption where
- peek = peekCaption
-
--- | Push Caption element
-pushCaption :: Caption -> Lua ()
-pushCaption (Caption shortCaption longCaption) = do
- Lua.newtable
- LuaUtil.addField "short" (Lua.Optional shortCaption)
- LuaUtil.addField "long" longCaption
-
--- | Peek Caption element
-peekCaption :: StackIndex -> Lua Caption
-peekCaption idx = Caption
- <$!> (Lua.fromOptional <$!> LuaUtil.rawField idx "short")
- <*> LuaUtil.rawField idx "long"
-
-instance Peekable ColWidth where
- peek idx = do
- width <- Lua.fromOptional <$!> Lua.peek idx
- return $! maybe ColWidthDefault ColWidth width
-
-instance Pushable ColWidth where
- push = \case
- (ColWidth w) -> Lua.push w
- ColWidthDefault -> Lua.pushnil
-
-instance Pushable Row where
- push (Row attr cells) = Lua.push (attr, cells)
-
-instance Peekable Row where
- peek = fmap (uncurry Row) . Lua.peek
-
-instance Pushable TableBody where
- push (TableBody attr (RowHeadColumns rowHeadColumns) head' body) = do
- Lua.newtable
- LuaUtil.addField "attr" attr
- LuaUtil.addField "row_head_columns" rowHeadColumns
- LuaUtil.addField "head" head'
- LuaUtil.addField "body" body
-
-instance Peekable TableBody where
- peek idx = TableBody
- <$!> LuaUtil.rawField idx "attr"
- <*> (RowHeadColumns <$!> LuaUtil.rawField idx "row_head_columns")
- <*> LuaUtil.rawField idx "head"
- <*> LuaUtil.rawField idx "body"
-
-instance Pushable TableHead where
- push (TableHead attr rows) = Lua.push (attr, rows)
-
-instance Peekable TableHead where
- peek = fmap (uncurry TableHead) . Lua.peek
-
-instance Pushable TableFoot where
- push (TableFoot attr cells) = Lua.push (attr, cells)
-
-instance Peekable TableFoot where
- peek = fmap (uncurry TableFoot) . Lua.peek
-
-instance Pushable Cell where
- push = pushCell
-
-instance Peekable Cell where
- peek = peekCell
-
-pushCell :: Cell -> Lua ()
-pushCell (Cell attr align (RowSpan rowSpan) (ColSpan colSpan) contents) = do
- Lua.newtable
- LuaUtil.addField "attr" attr
- LuaUtil.addField "alignment" align
- LuaUtil.addField "row_span" rowSpan
- LuaUtil.addField "col_span" colSpan
- LuaUtil.addField "contents" contents
-
-peekCell :: StackIndex -> Lua Cell
-peekCell idx = Cell
- <$!> (fromLuaAttr <$!> LuaUtil.rawField idx "attr")
- <*> LuaUtil.rawField idx "alignment"
- <*> (RowSpan <$!> LuaUtil.rawField idx "row_span")
- <*> (ColSpan <$!> LuaUtil.rawField idx "col_span")
- <*> LuaUtil.rawField idx "contents"
-
--- | Push an inline element to the top of the lua stack.
-pushInline :: Inline -> Lua ()
-pushInline = \case
- Cite citations lst -> pushViaConstructor "Cite" lst citations
- Code attr lst -> pushViaConstructor "Code" lst (LuaAttr attr)
- Emph inlns -> pushViaConstructor "Emph" inlns
- Underline inlns -> pushViaConstructor "Underline" inlns
- Image attr alt (src,tit) -> pushViaConstructor "Image" alt src tit (LuaAttr attr)
- LineBreak -> pushViaConstructor "LineBreak"
- Link attr lst (src,tit) -> pushViaConstructor "Link" lst src tit (LuaAttr attr)
- Note blcks -> pushViaConstructor "Note" blcks
- Math mty str -> pushViaConstructor "Math" mty str
- Quoted qt inlns -> pushViaConstructor "Quoted" qt inlns
- RawInline f cs -> pushViaConstructor "RawInline" f cs
- SmallCaps inlns -> pushViaConstructor "SmallCaps" inlns
- SoftBreak -> pushViaConstructor "SoftBreak"
- Space -> pushViaConstructor "Space"
- Span attr inlns -> pushViaConstructor "Span" inlns (LuaAttr attr)
- Str str -> pushViaConstructor "Str" str
- Strikeout inlns -> pushViaConstructor "Strikeout" inlns
- Strong inlns -> pushViaConstructor "Strong" inlns
- Subscript inlns -> pushViaConstructor "Subscript" inlns
- Superscript inlns -> pushViaConstructor "Superscript" inlns
-
--- | Return the value at the given index as inline if possible.
-peekInline :: StackIndex -> Lua Inline
-peekInline idx = defineHowTo "get Inline value" $ do
- tag <- LuaUtil.getTag idx
- case tag of
- "Cite" -> uncurry Cite <$!> elementContent
- "Code" -> withAttr Code <$!> elementContent
- "Emph" -> Emph <$!> elementContent
- "Underline" -> Underline <$!> elementContent
- "Image" -> (\(LuaAttr !attr, !lst, !tgt) -> Image attr lst tgt)
- <$!> elementContent
- "Link" -> (\(LuaAttr !attr, !lst, !tgt) -> Link attr lst tgt)
- <$!> elementContent
- "LineBreak" -> return LineBreak
- "Note" -> Note <$!> elementContent
- "Math" -> uncurry Math <$!> elementContent
- "Quoted" -> uncurry Quoted <$!> elementContent
- "RawInline" -> uncurry RawInline <$!> elementContent
- "SmallCaps" -> SmallCaps <$!> elementContent
- "SoftBreak" -> return SoftBreak
- "Space" -> return Space
- "Span" -> withAttr Span <$!> elementContent
- -- strict to Lua string is copied before gc
- "Str" -> Str <$!> elementContent
- "Strikeout" -> Strikeout <$!> elementContent
- "Strong" -> Strong <$!> elementContent
- "Subscript" -> Subscript <$!> elementContent
- "Superscript"-> Superscript <$!> elementContent
- _ -> Lua.throwMessage ("Unknown inline type: " <> tag)
- where
- -- Get the contents of an AST element.
- elementContent :: Peekable a => Lua a
- elementContent = LuaUtil.rawField idx "c"
-
-try :: Lua a -> Lua (Either PandocError a)
-try = Catch.try
-
-withAttr :: (Attr -> a -> b) -> (LuaAttr, a) -> b
-withAttr f (attributes, x) = f (fromLuaAttr attributes) x
-
--- | Wrapper for Attr
-newtype LuaAttr = LuaAttr { fromLuaAttr :: Attr }
-
-instance Pushable LuaAttr where
- push (LuaAttr (id', classes, kv)) =
- pushViaConstructor "Attr" id' classes kv
-
-instance Peekable LuaAttr where
- peek idx = defineHowTo "get Attr value" $! (LuaAttr <$!> Lua.peek idx)
-
--- | Wrapper for ListAttributes
-newtype LuaListAttributes = LuaListAttributes ListAttributes
-
-instance Pushable LuaListAttributes where
- push (LuaListAttributes (start, style, delimiter)) =
- pushViaConstructor "ListAttributes" start style delimiter
-
-instance Peekable LuaListAttributes where
- peek = defineHowTo "get ListAttributes value" .
- fmap LuaListAttributes . Lua.peek
diff --git a/src/Text/Pandoc/Lua/Marshaling/AnyValue.hs b/src/Text/Pandoc/Lua/Marshaling/AnyValue.hs
deleted file mode 100644
index 82e26b963..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/AnyValue.hs
+++ /dev/null
@@ -1,24 +0,0 @@
-{- |
- Module : Text.Pandoc.Lua.Marshaling.AnyValue
- Copyright : © 2017-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
-
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Helper type to work with raw Lua stack indices instead of unmarshaled
-values.
-
-TODO: Most of this module should be abstracted, factored out, and go
-into HsLua.
--}
-module Text.Pandoc.Lua.Marshaling.AnyValue (AnyValue (..)) where
-
-import Foreign.Lua (Peekable (peek), StackIndex)
-
--- | Dummy type to allow values of arbitrary Lua type. This just wraps
--- stack indices, using it requires extra care.
-newtype AnyValue = AnyValue StackIndex
-
-instance Peekable AnyValue where
- peek = return . AnyValue
diff --git a/src/Text/Pandoc/Lua/Marshaling/CommonState.hs b/src/Text/Pandoc/Lua/Marshaling/CommonState.hs
deleted file mode 100644
index 147197c5d..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/CommonState.hs
+++ /dev/null
@@ -1,102 +0,0 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-{-# LANGUAGE LambdaCase #-}
-{-# LANGUAGE OverloadedStrings #-}
-{- |
- Module : Text.Pandoc.Lua.Marshaling.CommonState
- Copyright : © 2012-2021 John MacFarlane
- © 2017-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Instances to marshal (push) and unmarshal (peek) the common state.
--}
-module Text.Pandoc.Lua.Marshaling.CommonState () where
-
-import Foreign.Lua (Lua, Peekable, Pushable)
-import Foreign.Lua.Types.Peekable (reportValueOnFailure)
-import Foreign.Lua.Userdata (ensureUserdataMetatable, pushAnyWithMetatable,
- toAnyWithName)
-import Text.Pandoc.Class (CommonState (..))
-import Text.Pandoc.Logging (LogMessage, showLogMessage)
-import Text.Pandoc.Lua.Marshaling.AnyValue (AnyValue (..))
-
-import qualified Data.Map as Map
-import qualified Data.Text as Text
-import qualified Foreign.Lua as Lua
-import qualified Text.Pandoc.Lua.Util as LuaUtil
-
--- | Name used by Lua for the @CommonState@ type.
-commonStateTypeName :: String
-commonStateTypeName = "Pandoc CommonState"
-
-instance Peekable CommonState where
- peek idx = reportValueOnFailure commonStateTypeName
- (`toAnyWithName` commonStateTypeName) idx
-
-instance Pushable CommonState where
- push st = pushAnyWithMetatable pushCommonStateMetatable st
- where
- pushCommonStateMetatable = ensureUserdataMetatable commonStateTypeName $ do
- LuaUtil.addFunction "__index" indexCommonState
- LuaUtil.addFunction "__pairs" pairsCommonState
-
-indexCommonState :: CommonState -> AnyValue -> Lua Lua.NumResults
-indexCommonState st (AnyValue idx) = Lua.ltype idx >>= \case
- Lua.TypeString -> 1 <$ (Lua.peek idx >>= pushField)
- _ -> 1 <$ Lua.pushnil
- where
- pushField :: Text.Text -> Lua ()
- pushField name = case lookup name commonStateFields of
- Just pushValue -> pushValue st
- Nothing -> Lua.pushnil
-
-pairsCommonState :: CommonState -> Lua Lua.NumResults
-pairsCommonState st = do
- Lua.pushHaskellFunction nextFn
- Lua.pushnil
- Lua.pushnil
- return 3
- where
- nextFn :: AnyValue -> AnyValue -> Lua Lua.NumResults
- nextFn _ (AnyValue idx) =
- Lua.ltype idx >>= \case
- Lua.TypeNil -> case commonStateFields of
- [] -> 2 <$ (Lua.pushnil *> Lua.pushnil)
- (key, pushValue):_ -> 2 <$ (Lua.push key *> pushValue st)
- Lua.TypeString -> do
- key <- Lua.peek idx
- case tail $ dropWhile ((/= key) . fst) commonStateFields of
- [] -> 2 <$ (Lua.pushnil *> Lua.pushnil)
- (nextKey, pushValue):_ -> 2 <$ (Lua.push nextKey *> pushValue st)
- _ -> 2 <$ (Lua.pushnil *> Lua.pushnil)
-
-commonStateFields :: [(Text.Text, CommonState -> Lua ())]
-commonStateFields =
- [ ("input_files", Lua.push . stInputFiles)
- , ("output_file", Lua.push . Lua.Optional . stOutputFile)
- , ("log", Lua.push . stLog)
- , ("request_headers", Lua.push . Map.fromList . stRequestHeaders)
- , ("resource_path", Lua.push . stResourcePath)
- , ("source_url", Lua.push . Lua.Optional . stSourceURL)
- , ("user_data_dir", Lua.push . Lua.Optional . stUserDataDir)
- , ("trace", Lua.push . stTrace)
- , ("verbosity", Lua.push . show . stVerbosity)
- ]
-
--- | Name used by Lua for the @CommonState@ type.
-logMessageTypeName :: String
-logMessageTypeName = "Pandoc LogMessage"
-
-instance Peekable LogMessage where
- peek idx = reportValueOnFailure logMessageTypeName
- (`toAnyWithName` logMessageTypeName) idx
-
-instance Pushable LogMessage where
- push msg = pushAnyWithMetatable pushLogMessageMetatable msg
- where
- pushLogMessageMetatable = ensureUserdataMetatable logMessageTypeName $
- LuaUtil.addFunction "__tostring" tostringLogMessage
-
-tostringLogMessage :: LogMessage -> Lua Text.Text
-tostringLogMessage = return . showLogMessage
diff --git a/src/Text/Pandoc/Lua/Marshaling/List.hs b/src/Text/Pandoc/Lua/Marshaling/List.hs
deleted file mode 100644
index 0446302a1..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/List.hs
+++ /dev/null
@@ -1,43 +0,0 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE MultiParamTypeClasses #-}
-{-# LANGUAGE UndecidableInstances #-}
-{- |
-Module : Text.Pandoc.Lua.Marshaling.List
-Copyright : © 2012-2021 John MacFarlane
- © 2017-2021 Albert Krewinkel
-License : GNU GPL, version 2 or above
-Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
-Stability : alpha
-
-Marshaling/unmarshaling instances for @pandoc.List@s.
--}
-module Text.Pandoc.Lua.Marshaling.List
- ( List (..)
- ) where
-
-import Data.Data (Data)
-import Foreign.Lua (Peekable, Pushable)
-import Text.Pandoc.Walk (Walkable (..))
-import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor)
-
-import qualified Foreign.Lua as Lua
-
--- | List wrapper which is marshalled as @pandoc.List@.
-newtype List a = List { fromList :: [a] }
- deriving (Data, Eq, Show)
-
-instance Pushable a => Pushable (List a) where
- push (List xs) =
- pushViaConstructor "List" xs
-
-instance Peekable a => Peekable (List a) where
- peek idx = defineHowTo "get List" $ do
- xs <- Lua.peek idx
- return $ List xs
-
--- List is just a wrapper, so we can reuse the walk instance for
--- unwrapped Hasekll lists.
-instance Walkable [a] b => Walkable (List a) b where
- walkM f = walkM (fmap fromList . f . List)
- query f = query (f . List)
diff --git a/src/Text/Pandoc/Lua/Marshaling/MediaBag.hs b/src/Text/Pandoc/Lua/Marshaling/MediaBag.hs
deleted file mode 100644
index 70bd010a0..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/MediaBag.hs
+++ /dev/null
@@ -1,73 +0,0 @@
-{- |
- Module : Text.Pandoc.Lua.Marshaling.MediaBag
- Copyright : © 2012-2021 John MacFarlane
- © 2017-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Instances to marshal (push) and unmarshal (peek) media data.
--}
-module Text.Pandoc.Lua.Marshaling.MediaBag (pushIterator) where
-
-import Foreign.Ptr (Ptr)
-import Foreign.StablePtr (StablePtr, deRefStablePtr, newStablePtr)
-import Foreign.Lua (Lua, NumResults, Peekable, Pushable, StackIndex)
-import Foreign.Lua.Types.Peekable (reportValueOnFailure)
-import Foreign.Lua.Userdata (ensureUserdataMetatable, pushAnyWithMetatable,
- toAnyWithName)
-import Text.Pandoc.MediaBag (MediaBag, mediaItems)
-import Text.Pandoc.MIME (MimeType)
-import Text.Pandoc.Lua.Marshaling.AnyValue (AnyValue (..))
-
-import qualified Data.ByteString.Lazy as BL
-import qualified Foreign.Lua as Lua
-import qualified Foreign.Storable as Storable
-
--- | A list of 'MediaBag' items.
-newtype MediaItems = MediaItems [(String, MimeType, BL.ByteString)]
-
-instance Pushable MediaItems where
- push = pushMediaItems
-
-instance Peekable MediaItems where
- peek = peekMediaItems
-
--- | Push an iterator triple to be used with Lua's @for@ loop construct.
--- Each iterator invocation returns a triple containing the item's
--- filename, MIME type, and content.
-pushIterator :: MediaBag -> Lua NumResults
-pushIterator mb = do
- Lua.pushHaskellFunction nextItem
- Lua.push (MediaItems $ mediaItems mb)
- Lua.pushnil
- return 3
-
--- | Lua type name for @'MediaItems'@.
-mediaItemsTypeName :: String
-mediaItemsTypeName = "pandoc MediaItems"
-
--- | Push a @MediaItems@ element to the stack.
-pushMediaItems :: MediaItems -> Lua ()
-pushMediaItems xs = pushAnyWithMetatable pushMT xs
- where
- pushMT = ensureUserdataMetatable mediaItemsTypeName (return ())
-
--- | Retrieve a @MediaItems@ element from the stack.
-peekMediaItems :: StackIndex -> Lua MediaItems
-peekMediaItems = reportValueOnFailure mediaItemsTypeName
- (`toAnyWithName` mediaItemsTypeName)
-
--- | Retrieve a list of items from an iterator state, return the first
--- item (if present), and advance the state.
-nextItem :: Ptr (StablePtr MediaItems) -> AnyValue -> Lua NumResults
-nextItem ptr _ = do
- (MediaItems items) <- Lua.liftIO $ deRefStablePtr =<< Storable.peek ptr
- case items of
- [] -> 2 <$ (Lua.pushnil *> Lua.pushnil)
- (key, mt, content):xs -> do
- Lua.liftIO $ Storable.poke ptr =<< newStablePtr (MediaItems xs)
- Lua.push key
- Lua.push mt
- Lua.push content
- return 3
diff --git a/src/Text/Pandoc/Lua/Marshaling/PandocError.hs b/src/Text/Pandoc/Lua/Marshaling/PandocError.hs
deleted file mode 100644
index f698704e0..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/PandocError.hs
+++ /dev/null
@@ -1,65 +0,0 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-{-# LANGUAGE LambdaCase #-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{- |
- Module : Text.Pandoc.Lua.Marshaling.PandocError
- Copyright : © 2020-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
-
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Marshaling of @'PandocError'@ values.
--}
-module Text.Pandoc.Lua.Marshaling.PandocError
- ( peekPandocError
- , pushPandocError
- )
- where
-
-import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
-import Text.Pandoc.Error (PandocError (PandocLuaError))
-
-import qualified Foreign.Lua as Lua
-import qualified Foreign.Lua.Userdata as Lua
-import qualified Text.Pandoc.Lua.Util as LuaUtil
-import qualified Text.Pandoc.UTF8 as UTF8
-
--- | Userdata name used by Lua for the @PandocError@ type.
-pandocErrorName :: String
-pandocErrorName = "pandoc error"
-
--- | Peek a @'PandocError'@ element to the Lua stack.
-pushPandocError :: PandocError -> Lua ()
-pushPandocError = Lua.pushAnyWithMetatable pushPandocErrorMT
- where
- pushPandocErrorMT = Lua.ensureUserdataMetatable pandocErrorName $
- LuaUtil.addFunction "__tostring" __tostring
-
--- | Retrieve a @'PandocError'@ from the Lua stack.
-peekPandocError :: StackIndex -> Lua PandocError
-peekPandocError idx = Lua.ltype idx >>= \case
- Lua.TypeUserdata -> do
- errMb <- Lua.toAnyWithName idx pandocErrorName
- return $ case errMb of
- Just err -> err
- Nothing -> PandocLuaError "could not retrieve original error"
- _ -> do
- Lua.pushvalue idx
- msg <- Lua.state >>= \l -> Lua.liftIO (Lua.errorMessage l)
- return $ PandocLuaError (UTF8.toText msg)
-
--- | Convert to string.
-__tostring :: PandocError -> Lua String
-__tostring = return . show
-
---
--- Instances
---
-
-instance Pushable PandocError where
- push = pushPandocError
-
-instance Peekable PandocError where
- peek = peekPandocError
diff --git a/src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs b/src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs
deleted file mode 100644
index dd7bf2e61..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/ReaderOptions.hs
+++ /dev/null
@@ -1,79 +0,0 @@
-{-# LANGUAGE LambdaCase #-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-{- |
- Module : Text.Pandoc.Lua.Marshaling.ReaderOptions
- Copyright : © 2012-2021 John MacFarlane
- © 2017-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
-
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Marshaling instance for ReaderOptions and its components.
--}
-module Text.Pandoc.Lua.Marshaling.ReaderOptions () where
-
-import Data.Data (showConstr, toConstr)
-import Foreign.Lua (Lua, Pushable)
-import Text.Pandoc.Extensions (Extensions)
-import Text.Pandoc.Lua.Marshaling.AnyValue (AnyValue (..))
-import Text.Pandoc.Lua.Marshaling.CommonState ()
-import Text.Pandoc.Options (ReaderOptions (..), TrackChanges)
-
-import qualified Data.Set as Set
-import qualified Data.Text as Text
-import qualified Foreign.Lua as Lua
-import qualified Text.Pandoc.Lua.Util as LuaUtil
-
---
--- Reader Options
---
-instance Pushable Extensions where
- push exts = Lua.push (show exts)
-
-instance Pushable TrackChanges where
- push = Lua.push . showConstr . toConstr
-
-instance Pushable ReaderOptions where
- push ro = do
- let ReaderOptions
- (extensions :: Extensions)
- (standalone :: Bool)
- (columns :: Int)
- (tabStop :: Int)
- (indentedCodeClasses :: [Text.Text])
- (abbreviations :: Set.Set Text.Text)
- (defaultImageExtension :: Text.Text)
- (trackChanges :: TrackChanges)
- (stripComments :: Bool)
- = ro
- Lua.newtable
- LuaUtil.addField "extensions" extensions
- LuaUtil.addField "standalone" standalone
- LuaUtil.addField "columns" columns
- LuaUtil.addField "tab_stop" tabStop
- LuaUtil.addField "indented_code_classes" indentedCodeClasses
- LuaUtil.addField "abbreviations" abbreviations
- LuaUtil.addField "default_image_extension" defaultImageExtension
- LuaUtil.addField "track_changes" trackChanges
- LuaUtil.addField "strip_comments" stripComments
-
- -- add metatable
- let indexReaderOptions :: AnyValue -> AnyValue -> Lua Lua.NumResults
- indexReaderOptions _tbl (AnyValue key) = do
- Lua.ltype key >>= \case
- Lua.TypeString -> Lua.peek key >>= \case
- ("defaultImageExtension" :: Text.Text)
- -> Lua.push defaultImageExtension
- "indentedCodeClasses" -> Lua.push indentedCodeClasses
- "stripComments" -> Lua.push stripComments
- "tabStop" -> Lua.push tabStop
- "trackChanges" -> Lua.push trackChanges
- _ -> Lua.pushnil
- _ -> Lua.pushnil
- return 1
- Lua.newtable
- LuaUtil.addFunction "__index" indexReaderOptions
- Lua.setmetatable (Lua.nthFromTop 2)
diff --git a/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs b/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
deleted file mode 100644
index 6d43039fa..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
+++ /dev/null
@@ -1,59 +0,0 @@
-{- |
- Module : Text.Pandoc.Lua.Marshaling.SimpleTable
- Copyright : © 2020-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
-
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Definition and marshaling of the 'SimpleTable' data type used as a
-convenience type when dealing with tables.
--}
-module Text.Pandoc.Lua.Marshaling.SimpleTable
- ( SimpleTable (..)
- , peekSimpleTable
- , pushSimpleTable
- )
- where
-
-import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
-import Text.Pandoc.Definition
-import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor, rawField)
-import Text.Pandoc.Lua.Marshaling.AST ()
-
-import qualified Foreign.Lua as Lua
-
--- | A simple (legacy-style) table.
-data SimpleTable = SimpleTable
- { simpleTableCaption :: [Inline]
- , simpleTableAlignments :: [Alignment]
- , simpleTableColumnWidths :: [Double]
- , simpleTableHeader :: [[Block]]
- , simpleTableBody :: [[[Block]]]
- }
-
-instance Pushable SimpleTable where
- push = pushSimpleTable
-
-instance Peekable SimpleTable where
- peek = peekSimpleTable
-
--- | Push a simple table to the stack by calling the
--- @pandoc.SimpleTable@ constructor.
-pushSimpleTable :: SimpleTable -> Lua ()
-pushSimpleTable tbl = pushViaConstructor "SimpleTable"
- (simpleTableCaption tbl)
- (simpleTableAlignments tbl)
- (simpleTableColumnWidths tbl)
- (simpleTableHeader tbl)
- (simpleTableBody tbl)
-
--- | Retrieve a simple table from the stack.
-peekSimpleTable :: StackIndex -> Lua SimpleTable
-peekSimpleTable idx = defineHowTo "get SimpleTable" $
- SimpleTable
- <$> rawField idx "caption"
- <*> rawField idx "aligns"
- <*> rawField idx "widths"
- <*> rawField idx "headers"
- <*> rawField idx "rows"
diff --git a/src/Text/Pandoc/Lua/Marshaling/Version.hs b/src/Text/Pandoc/Lua/Marshaling/Version.hs
deleted file mode 100644
index 4f4ffac51..000000000
--- a/src/Text/Pandoc/Lua/Marshaling/Version.hs
+++ /dev/null
@@ -1,154 +0,0 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-{-# LANGUAGE LambdaCase #-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{- |
- Module : Text.Pandoc.Lua.Marshaling.Version
- Copyright : © 2019-2021 Albert Krewinkel
- License : GNU GPL, version 2 or above
-
- Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-
-Marshaling of @'Version'@s. The marshaled elements can be compared using
-default comparison operators (like @>@ and @<=@).
--}
-module Text.Pandoc.Lua.Marshaling.Version
- ( peekVersion
- , pushVersion
- )
- where
-
-import Data.Text (Text)
-import Data.Maybe (fromMaybe)
-import Data.Version (Version (..), makeVersion, parseVersion, showVersion)
-import Foreign.Lua (Lua, Optional (..), NumResults,
- Peekable, Pushable, StackIndex)
-import Foreign.Lua.Types.Peekable (reportValueOnFailure)
-import Foreign.Lua.Userdata (ensureUserdataMetatable, pushAnyWithMetatable,
- toAnyWithName)
-import Safe (atMay, lastMay)
-import Text.Pandoc.Lua.Marshaling.AnyValue (AnyValue (..))
-import Text.ParserCombinators.ReadP (readP_to_S)
-
-import qualified Foreign.Lua as Lua
-import qualified Text.Pandoc.Lua.Util as LuaUtil
-
--- | Push a @'Version'@ element to the Lua stack.
-pushVersion :: Version -> Lua ()
-pushVersion version = pushAnyWithMetatable pushVersionMT version
- where
- pushVersionMT = ensureUserdataMetatable versionTypeName $ do
- LuaUtil.addFunction "__eq" __eq
- LuaUtil.addFunction "__le" __le
- LuaUtil.addFunction "__lt" __lt
- LuaUtil.addFunction "__len" __len
- LuaUtil.addFunction "__index" __index
- LuaUtil.addFunction "__pairs" __pairs
- LuaUtil.addFunction "__tostring" __tostring
-
-instance Pushable Version where
- push = pushVersion
-
-peekVersion :: StackIndex -> Lua Version
-peekVersion idx = Lua.ltype idx >>= \case
- Lua.TypeString -> do
- versionStr <- Lua.peek idx
- let parses = readP_to_S parseVersion versionStr
- case lastMay parses of
- Just (v, "") -> return v
- _ -> Lua.throwMessage $ "could not parse as Version: " ++ versionStr
-
- Lua.TypeUserdata ->
- reportValueOnFailure versionTypeName
- (`toAnyWithName` versionTypeName)
- idx
- Lua.TypeNumber -> do
- n <- Lua.peek idx
- return (makeVersion [n])
-
- Lua.TypeTable ->
- makeVersion <$> Lua.peek idx
-
- _ ->
- Lua.throwMessage "could not peek Version"
-
-instance Peekable Version where
- peek = peekVersion
-
--- | Name used by Lua for the @CommonState@ type.
-versionTypeName :: String
-versionTypeName = "HsLua Version"
-
-__eq :: Version -> Version -> Lua Bool
-__eq v1 v2 = return (v1 == v2)
-
-__le :: Version -> Version -> Lua Bool
-__le v1 v2 = return (v1 <= v2)
-
-__lt :: Version -> Version -> Lua Bool
-__lt v1 v2 = return (v1 < v2)
-
--- | Get number of version components.
-__len :: Version -> Lua Int
-__len = return . length . versionBranch
-
--- | Access fields.
-__index :: Version -> AnyValue -> Lua NumResults
-__index v (AnyValue k) = do
- ty <- Lua.ltype k
- case ty of
- Lua.TypeNumber -> do
- n <- Lua.peek k
- let versionPart = atMay (versionBranch v) (n - 1)
- Lua.push (Lua.Optional versionPart)
- return 1
- Lua.TypeString -> do
- (str :: Text) <- Lua.peek k
- if str == "must_be_at_least"
- then 1 <$ Lua.pushHaskellFunction must_be_at_least
- else 1 <$ Lua.pushnil
- _ -> 1 <$ Lua.pushnil
-
--- | Create iterator.
-__pairs :: Version -> Lua NumResults
-__pairs v = do
- Lua.pushHaskellFunction nextFn
- Lua.pushnil
- Lua.pushnil
- return 3
- where
- nextFn :: AnyValue -> Optional Int -> Lua Lua.NumResults
- nextFn _ (Optional key) =
- case key of
- Nothing -> case versionBranch v of
- [] -> 2 <$ (Lua.pushnil *> Lua.pushnil)
- n:_ -> 2 <$ (Lua.push (1 :: Int) *> Lua.push n)
- Just n -> case atMay (versionBranch v) n of
- Nothing -> 2 <$ (Lua.pushnil *> Lua.pushnil)
- Just b -> 2 <$ (Lua.push (n + 1) *> Lua.push b)
-
--- | Convert to string.
-__tostring :: Version -> Lua String
-__tostring v = return (showVersion v)
-
--- | Default error message when a version is too old. This message is
--- formatted in Lua with the expected and actual versions as arguments.
-versionTooOldMessage :: String
-versionTooOldMessage = "expected version %s or newer, got %s"
-
--- | Throw an error if this version is older than the given version.
--- FIXME: This function currently requires the string library to be
--- loaded.
-must_be_at_least :: Version -> Version -> Optional String -> Lua NumResults
-must_be_at_least actual expected optMsg = do
- let msg = fromMaybe versionTooOldMessage (fromOptional optMsg)
- if expected <= actual
- then return 0
- else do
- Lua.getglobal' "string.format"
- Lua.push msg
- Lua.push (showVersion expected)
- Lua.push (showVersion actual)
- Lua.call 3 1
- Lua.error
diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs
index 3eed50fca..fb055101e 100644
--- a/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -1,103 +1,126 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.MediaBag
Copyright : Copyright © 2017-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
-
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-The lua module @pandoc.mediabag@.
+The Lua module @pandoc.mediabag@.
-}
module Text.Pandoc.Lua.Module.MediaBag
- ( pushModule
+ ( documentedModule
) where
import Prelude hiding (lookup)
-import Control.Monad (zipWithM_)
-import Foreign.Lua (Lua, NumResults, Optional)
+import Data.Maybe (fromMaybe)
+import HsLua ( LuaE, DocumentedFunction, Module (..)
+ , (<#>), (###), (=#>), (=?>), defun, functionResult
+ , optionalParameter , parameter)
import Text.Pandoc.Class.CommonState (CommonState (..))
import Text.Pandoc.Class.PandocMonad (fetchItem, getMediaBag, modifyCommonState,
setMediaBag)
-import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Marshaling.MediaBag (pushIterator)
-import Text.Pandoc.Lua.PandocLua (PandocLua (..), liftPandocLua, addFunction)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+import Text.Pandoc.Lua.Orphans ()
+import Text.Pandoc.Lua.PandocLua (unPandocLua)
import Text.Pandoc.MIME (MimeType)
import qualified Data.ByteString.Lazy as BL
-import qualified Data.Text as T
-import qualified Foreign.Lua as Lua
+import qualified HsLua as Lua
import qualified Text.Pandoc.MediaBag as MB
--
-- MediaBag submodule
--
-pushModule :: PandocLua NumResults
-pushModule = do
- liftPandocLua Lua.newtable
- addFunction "delete" delete
- addFunction "empty" empty
- addFunction "insert" insert
- addFunction "items" items
- addFunction "lookup" lookup
- addFunction "list" list
- addFunction "fetch" fetch
- return 1
+documentedModule :: Module PandocError
+documentedModule = Module
+ { moduleName = "pandoc.mediabag"
+ , moduleDescription = "mediabag access"
+ , moduleFields = []
+ , moduleFunctions =
+ [ delete
+ , empty
+ , fetch
+ , insert
+ , items
+ , list
+ , lookup
+ ]
+ , moduleOperations = []
+ }
-- | Delete a single item from the media bag.
-delete :: FilePath -> PandocLua NumResults
-delete fp = 0 <$ modifyCommonState
- (\st -> st { stMediaBag = MB.deleteMedia fp (stMediaBag st) })
+delete :: DocumentedFunction PandocError
+delete = defun "delete"
+ ### (\fp -> unPandocLua $ modifyCommonState
+ (\st -> st { stMediaBag = MB.deleteMedia fp (stMediaBag st) }))
+ <#> parameter Lua.peekString "string" "filepath" "filename of item to delete"
+ =#> []
+
-- | Delete all items from the media bag.
-empty :: PandocLua NumResults
-empty = 0 <$ modifyCommonState (\st -> st { stMediaBag = mempty })
+empty :: DocumentedFunction PandocError
+empty = defun "empty"
+ ### unPandocLua (modifyCommonState (\st -> st { stMediaBag = mempty }))
+ =#> []
-- | Insert a new item into the media bag.
-insert :: FilePath
- -> Optional MimeType
- -> BL.ByteString
- -> PandocLua NumResults
-insert fp optionalMime contents = do
- mb <- getMediaBag
- setMediaBag $ MB.insertMedia fp (Lua.fromOptional optionalMime) contents mb
- return (Lua.NumResults 0)
+insert :: DocumentedFunction PandocError
+insert = defun "insert"
+ ### (\fp mmime contents -> unPandocLua $ do
+ mb <- getMediaBag
+ setMediaBag $ MB.insertMedia fp mmime contents mb
+ return (Lua.NumResults 0))
+ <#> parameter Lua.peekString "string" "filepath" "item file path"
+ <#> optionalParameter Lua.peekText "string" "mimetype" "the item's MIME type"
+ <#> parameter Lua.peekLazyByteString "string" "contents" "binary contents"
+ =?> "Nothing"
-- | Returns iterator values to be used with a Lua @for@ loop.
-items :: PandocLua NumResults
-items = getMediaBag >>= liftPandocLua . pushIterator
+items :: DocumentedFunction PandocError
+items = defun "items"
+ ### (do
+ mb <-unPandocLua getMediaBag
+ let pushItem (fp, mimetype, contents) = do
+ Lua.pushString fp
+ Lua.pushText mimetype
+ Lua.pushByteString $ BL.toStrict contents
+ return (Lua.NumResults 3)
+ Lua.pushIterator pushItem (MB.mediaItems mb))
+ =?> "Iterator triple"
-lookup :: FilePath
- -> PandocLua NumResults
-lookup fp = do
- res <- MB.lookupMedia fp <$> getMediaBag
- liftPandocLua $ case res of
- Nothing -> 1 <$ Lua.pushnil
- Just item -> do
- Lua.push $ MB.mediaMimeType item
- Lua.push $ MB.mediaContents item
- return 2
+-- | Function to lookup a value in the mediabag.
+lookup :: DocumentedFunction PandocError
+lookup = defun "lookup"
+ ### (\fp -> unPandocLua (MB.lookupMedia fp <$> getMediaBag) >>= \case
+ Nothing -> 1 <$ Lua.pushnil
+ Just item -> 2 <$ do
+ Lua.pushText $ MB.mediaMimeType item
+ Lua.pushLazyByteString $ MB.mediaContents item)
+ <#> parameter Lua.peekString "string" "filepath" "path of item to lookup"
+ =?> "MIME type and contents"
-list :: PandocLua NumResults
-list = do
- dirContents <- MB.mediaDirectory <$> getMediaBag
- liftPandocLua $ do
- Lua.newtable
- zipWithM_ addEntry [1..] dirContents
- return 1
+-- | Function listing all mediabag items.
+list :: DocumentedFunction PandocError
+list = defun "list"
+ ### (unPandocLua (MB.mediaDirectory <$> getMediaBag))
+ =#> functionResult (pushPandocList pushEntry) "table" "list of entry triples"
where
- addEntry :: Lua.Integer -> (FilePath, MimeType, Int) -> Lua ()
- addEntry idx (fp, mimeType, contentLength) = do
+ pushEntry :: (FilePath, MimeType, Int) -> LuaE PandocError ()
+ pushEntry (fp, mimeType, contentLength) = do
Lua.newtable
- Lua.push ("path" :: T.Text) *> Lua.push fp *> Lua.rawset (-3)
- Lua.push ("type" :: T.Text) *> Lua.push mimeType *> Lua.rawset (-3)
- Lua.push ("length" :: T.Text) *> Lua.push contentLength *> Lua.rawset (-3)
- Lua.rawseti (-2) idx
+ Lua.pushName "path" *> Lua.pushString fp *> Lua.rawset (-3)
+ Lua.pushName "type" *> Lua.pushText mimeType *> Lua.rawset (-3)
+ Lua.pushName "length" *> Lua.pushIntegral contentLength *> Lua.rawset (-3)
-fetch :: T.Text
- -> PandocLua NumResults
-fetch src = do
- (bs, mimeType) <- fetchItem src
- liftPandocLua . Lua.push $ maybe "" T.unpack mimeType
- liftPandocLua $ Lua.push bs
- return 2 -- returns 2 values: contents, mimetype
+-- | Lua function to retrieve a new item.
+fetch :: DocumentedFunction PandocError
+fetch = defun "fetch"
+ ### (\src -> do
+ (bs, mimeType) <- unPandocLua $ fetchItem src
+ Lua.pushText $ fromMaybe "" mimeType
+ Lua.pushByteString bs
+ return 2)
+ <#> parameter Lua.peekText "string" "src" "URI to fetch"
+ =?> "Returns two string values: the fetched contents and the mimetype."
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index 5c14b3a30..20c2f5af5 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -1,5 +1,8 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Module.Pandoc
Copyright : Copyright © 2017-2021 Albert Krewinkel
@@ -12,32 +15,37 @@ Pandoc module for lua.
-}
module Text.Pandoc.Lua.Module.Pandoc
( pushModule
+ , documentedModule
) where
import Prelude hiding (read)
-import Control.Monad (when)
+import Control.Monad (forM_, when)
+import Control.Monad.Catch (catch, throwM)
import Control.Monad.Except (throwError)
+import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
-import Foreign.Lua (Lua, NumResults, Optional, Peekable, Pushable)
+import Data.Proxy (Proxy (Proxy))
+import HsLua hiding (pushModule)
+import HsLua.Class.Peekable (PeekError)
import System.Exit (ExitCode (..))
import Text.Pandoc.Class.PandocIO (runIO)
-import Text.Pandoc.Definition (Block, Inline)
-import Text.Pandoc.Lua.Filter (LuaFilter, SingletonsList (..), walkInlines,
- walkInlineLists, walkBlocks, walkBlockLists)
-import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Marshaling.List (List (..))
-import Text.Pandoc.Lua.PandocLua (PandocLua, addFunction, liftPandocLua,
- loadDefaultModule)
-import Text.Pandoc.Walk (Walkable)
+import Text.Pandoc.Definition
+import Text.Pandoc.Lua.Orphans ()
+import Text.Pandoc.Lua.Marshal.AST
+import Text.Pandoc.Lua.Marshal.Filter (peekFilter)
+import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions
+ , pushReaderOptions)
+import Text.Pandoc.Lua.Module.Utils (sha1)
+import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua)
import Text.Pandoc.Options (ReaderOptions (readerExtensions))
import Text.Pandoc.Process (pipeProcess)
import Text.Pandoc.Readers (Reader (..), getReader)
+import qualified HsLua as Lua
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Text as T
-import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.Lua.Util as LuaUtil
import Text.Pandoc.Error
@@ -45,55 +53,164 @@ import Text.Pandoc.Error
-- module to be loadable.
pushModule :: PandocLua NumResults
pushModule = do
- loadDefaultModule "pandoc"
- addFunction "read" read
- addFunction "pipe" pipe
- addFunction "walk_block" walk_block
- addFunction "walk_inline" walk_inline
+ liftPandocLua $ Lua.pushModule documentedModule
return 1
-walkElement :: (Walkable (SingletonsList Inline) a,
- Walkable (SingletonsList Block) a,
- Walkable (List Inline) a,
- Walkable (List Block) a)
- => a -> LuaFilter -> PandocLua a
-walkElement x f = liftPandocLua $
- walkInlines f x >>= walkInlineLists f >>= walkBlocks f >>= walkBlockLists f
-
-walk_inline :: Inline -> LuaFilter -> PandocLua Inline
-walk_inline = walkElement
-
-walk_block :: Block -> LuaFilter -> PandocLua Block
-walk_block = walkElement
-
-read :: T.Text -> Optional T.Text -> PandocLua NumResults
-read content formatSpecOrNil = liftPandocLua $ do
- let formatSpec = fromMaybe "markdown" (Lua.fromOptional formatSpecOrNil)
- res <- Lua.liftIO . runIO $
- getReader formatSpec >>= \(rdr,es) ->
- case rdr of
- TextReader r ->
- r def{ readerExtensions = es } content
- _ -> throwError $ PandocSomeError
- "Only textual formats are supported"
- case res of
- Right pd -> (1 :: NumResults) <$ Lua.push pd -- success, push Pandoc
- Left (PandocUnknownReaderError f) -> Lua.raiseError $
- "Unknown reader: " <> f
- Left (PandocUnsupportedExtensionError e f) -> Lua.raiseError $
- "Extension " <> e <> " not supported for " <> f
- Left e -> Lua.raiseError $ show e
-
--- | Pipes input through a command.
-pipe :: String -- ^ path to executable
- -> [String] -- ^ list of arguments
- -> BL.ByteString -- ^ input passed to process via stdin
- -> PandocLua NumResults
-pipe command args input = liftPandocLua $ do
- (ec, output) <- Lua.liftIO $ pipeProcess Nothing command args input
- case ec of
- ExitSuccess -> 1 <$ Lua.push output
- ExitFailure n -> Lua.raiseError (PipeError (T.pack command) n output)
+documentedModule :: Module PandocError
+documentedModule = Module
+ { moduleName = "pandoc"
+ , moduleDescription = T.unlines
+ [ "Lua functions for pandoc scripts; includes constructors for"
+ , "document elements, functions to parse text in a given"
+ , "format, and functions to filter and modify a subtree."
+ ]
+ , moduleFields = stringConstants ++ [inlineField, blockField]
+ , moduleOperations = []
+ , moduleFunctions = mconcat
+ [ functions
+ , otherConstructors
+ , blockConstructors
+ , inlineConstructors
+ , metaValueConstructors
+ ]
+ }
+
+-- | Inline table field
+inlineField :: Field PandocError
+inlineField = Field
+ { fieldName = "Inline"
+ , fieldDescription = "Inline constructors, nested under 'constructors'."
+ -- the nesting happens for historical reasons and should probably be
+ -- changed.
+ , fieldPushValue = pushWithConstructorsSubtable inlineConstructors
+ }
+
+-- | @Block@ module field
+blockField :: Field PandocError
+blockField = Field
+ { fieldName = "Block"
+ , fieldDescription = "Inline constructors, nested under 'constructors'."
+ -- the nesting happens for historical reasons and should probably be
+ -- changed.
+ , fieldPushValue = pushWithConstructorsSubtable blockConstructors
+ }
+
+pushWithConstructorsSubtable :: [DocumentedFunction PandocError]
+ -> LuaE PandocError ()
+pushWithConstructorsSubtable constructors = do
+ newtable -- Field table
+ newtable -- constructor table
+ pushName "constructor" *> pushvalue (nth 2) *> rawset (nth 4)
+ forM_ constructors $ \fn -> do
+ pushName (functionName fn)
+ pushDocumentedFunction fn
+ rawset (nth 3)
+ pop 1 -- pop constructor table
+
+otherConstructors :: LuaError e => [DocumentedFunction e]
+otherConstructors =
+ [ mkPandoc
+ , mkMeta
+ , mkAttr
+ , mkAttributeList
+ , mkBlocks
+ , mkCitation
+ , mkCell
+ , mkRow
+ , mkTableHead
+ , mkTableFoot
+ , mkInlines
+ , mkListAttributes
+ , mkSimpleTable
+
+ , defun "ReaderOptions"
+ ### liftPure id
+ <#> parameter peekReaderOptions "ReaderOptions|table" "opts" "reader options"
+ =#> functionResult pushReaderOptions "ReaderOptions" "new object"
+ #? "Creates a new ReaderOptions value."
+ ]
+
+stringConstants :: [Field e]
+stringConstants =
+ let constrs :: forall a. Data a => Proxy a -> [String]
+ constrs _ = map showConstr . dataTypeConstrs . dataTypeOf @a $ undefined
+ nullaryConstructors = mconcat
+ [ constrs (Proxy @ListNumberStyle)
+ , constrs (Proxy @ListNumberDelim)
+ , constrs (Proxy @QuoteType)
+ , constrs (Proxy @MathType)
+ , constrs (Proxy @Alignment)
+ , constrs (Proxy @CitationMode)
+ ]
+ toField s = Field
+ { fieldName = T.pack s
+ , fieldDescription = T.pack s
+ , fieldPushValue = pushString s
+ }
+ in map toField nullaryConstructors
+
+functions :: [DocumentedFunction PandocError]
+functions =
+ [ defun "pipe"
+ ### (\command args input -> do
+ (ec, output) <- Lua.liftIO $ pipeProcess Nothing command args input
+ `catch` (throwM . PandocIOError "pipe")
+ case ec of
+ ExitSuccess -> 1 <$ Lua.pushLazyByteString output
+ ExitFailure n -> do
+ pushPipeError (PipeError (T.pack command) n output)
+ Lua.error)
+ <#> parameter peekString "string" "command" "path to executable"
+ <#> parameter (peekList peekString) "{string,...}" "args"
+ "list of arguments"
+ <#> parameter peekLazyByteString "string" "input"
+ "input passed to process via stdin"
+ =?> "output string, or error triple"
+
+ , defun "read"
+ ### (\content mformatspec mreaderOptions -> do
+ let formatSpec = fromMaybe "markdown" mformatspec
+ readerOptions = fromMaybe def mreaderOptions
+ res <- Lua.liftIO . runIO $ getReader formatSpec >>= \case
+ (TextReader r, es) -> r readerOptions{ readerExtensions = es }
+ content
+ _ -> throwError $ PandocSomeError
+ "Only textual formats are supported"
+ case res of
+ Right pd -> return pd -- success, got a Pandoc document
+ Left (PandocUnknownReaderError f) ->
+ Lua.failLua . T.unpack $ "Unknown reader: " <> f
+ Left (PandocUnsupportedExtensionError e f) ->
+ Lua.failLua . T.unpack $
+ "Extension " <> e <> " not supported for " <> f
+ Left e ->
+ throwM e)
+ <#> parameter peekText "string" "content" "text to parse"
+ <#> optionalParameter peekText "string" "formatspec" "format and extensions"
+ <#> optionalParameter peekReaderOptions "ReaderOptions" "reader_options"
+ "reader options"
+ =#> functionResult pushPandoc "Pandoc" "result document"
+
+ , sha1
+
+ , defun "walk_block"
+ ### walkElement
+ <#> parameter peekBlockFuzzy "Block" "block" "element to traverse"
+ <#> parameter peekFilter "Filter" "lua_filter" "filter functions"
+ =#> functionResult pushBlock "Block" "modified Block"
+
+ , defun "walk_inline"
+ ### walkElement
+ <#> parameter peekInlineFuzzy "Inline" "inline" "element to traverse"
+ <#> parameter peekFilter "Filter" "lua_filter" "filter functions"
+ =#> functionResult pushInline "Inline" "modified Inline"
+ ]
+ where
+ walkElement x f =
+ walkInlineSplicing f x
+ >>= walkInlinesStraight f
+ >>= walkBlockSplicing f
+ >>= walkBlocksStraight f
data PipeError = PipeError
{ pipeErrorCommand :: T.Text
@@ -101,29 +218,34 @@ data PipeError = PipeError
, pipeErrorOutput :: BL.ByteString
}
-instance Peekable PipeError where
- peek idx =
- PipeError
- <$> (Lua.getfield idx "command" *> Lua.peek (-1) <* Lua.pop 1)
- <*> (Lua.getfield idx "error_code" *> Lua.peek (-1) <* Lua.pop 1)
- <*> (Lua.getfield idx "output" *> Lua.peek (-1) <* Lua.pop 1)
-
-instance Pushable PipeError where
- push pipeErr = do
- Lua.newtable
- LuaUtil.addField "command" (pipeErrorCommand pipeErr)
- LuaUtil.addField "error_code" (pipeErrorCode pipeErr)
- LuaUtil.addField "output" (pipeErrorOutput pipeErr)
- pushPipeErrorMetaTable
- Lua.setmetatable (-2)
- where
- pushPipeErrorMetaTable :: Lua ()
- pushPipeErrorMetaTable = do
- v <- Lua.newmetatable "pandoc pipe error"
- when v $ LuaUtil.addFunction "__tostring" pipeErrorMessage
-
- pipeErrorMessage :: PipeError -> Lua BL.ByteString
- pipeErrorMessage (PipeError cmd errorCode output) = return $ mconcat
+peekPipeError :: PeekError e => StackIndex -> LuaE e PipeError
+peekPipeError idx =
+ PipeError
+ <$> (Lua.getfield idx "command" *> Lua.peek (-1) <* Lua.pop 1)
+ <*> (Lua.getfield idx "error_code" *> Lua.peek (-1) <* Lua.pop 1)
+ <*> (Lua.getfield idx "output" *> Lua.peek (-1) <* Lua.pop 1)
+
+pushPipeError :: PeekError e => Pusher e PipeError
+pushPipeError pipeErr = do
+ Lua.newtable
+ LuaUtil.addField "command" (pipeErrorCommand pipeErr)
+ LuaUtil.addField "error_code" (pipeErrorCode pipeErr)
+ LuaUtil.addField "output" (pipeErrorOutput pipeErr)
+ pushPipeErrorMetaTable
+ Lua.setmetatable (-2)
+ where
+ pushPipeErrorMetaTable :: PeekError e => LuaE e ()
+ pushPipeErrorMetaTable = do
+ v <- Lua.newmetatable "pandoc pipe error"
+ when v $ do
+ pushName "__tostring"
+ pushHaskellFunction pipeErrorMessage
+ rawset (nth 3)
+
+ pipeErrorMessage :: PeekError e => LuaE e NumResults
+ pipeErrorMessage = do
+ (PipeError cmd errorCode output) <- peekPipeError (nthBottom 1)
+ pushByteString . BSL.toStrict . BSL.concat $
[ BSL.pack "Error running "
, BSL.pack $ T.unpack cmd
, BSL.pack " (error code "
@@ -131,3 +253,4 @@ instance Pushable PipeError where
, BSL.pack "): "
, if output == mempty then BSL.pack "<no output>" else output
]
+ return (NumResults 1)
diff --git a/src/Text/Pandoc/Lua/Module/System.hs b/src/Text/Pandoc/Lua/Module/System.hs
index bd35babaf..e329a0125 100644
--- a/src/Text/Pandoc/Lua/Module/System.hs
+++ b/src/Text/Pandoc/Lua/Module/System.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Text.Pandoc.Lua.Module.System
Copyright : © 2019-2021 Albert Krewinkel
@@ -9,25 +11,28 @@
Pandoc's system Lua module.
-}
module Text.Pandoc.Lua.Module.System
- ( pushModule
+ ( documentedModule
) where
-import Foreign.Lua (Lua, NumResults)
-import Foreign.Lua.Module.System (arch, env, getwd, os,
- with_env, with_tmpdir, with_wd)
-import Text.Pandoc.Lua.Util (addFunction, addField)
-
-import qualified Foreign.Lua as Lua
+import HsLua
+import HsLua.Module.System
+ (arch, env, getwd, os, with_env, with_tmpdir, with_wd)
-- | Push the pandoc.system module on the Lua stack.
-pushModule :: Lua NumResults
-pushModule = do
- Lua.newtable
- addField "arch" arch
- addField "os" os
- addFunction "environment" env
- addFunction "get_working_directory" getwd
- addFunction "with_environment" with_env
- addFunction "with_temporary_directory" with_tmpdir
- addFunction "with_working_directory" with_wd
- return 1
+documentedModule :: LuaError e => Module e
+documentedModule = Module
+ { moduleName = "pandoc.system"
+ , moduleDescription = "system functions"
+ , moduleFields =
+ [ arch
+ , os
+ ]
+ , moduleFunctions =
+ [ setName "environment" env
+ , setName "get_working_directory" getwd
+ , setName "with_environment" with_env
+ , setName "with_temporary_directory" with_tmpdir
+ , setName "with_working_directory" with_wd
+ ]
+ , moduleOperations = []
+ }
diff --git a/src/Text/Pandoc/Lua/Module/Types.hs b/src/Text/Pandoc/Lua/Module/Types.hs
index bb4f02c3c..f16737f63 100644
--- a/src/Text/Pandoc/Lua/Module/Types.hs
+++ b/src/Text/Pandoc/Lua/Module/Types.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.Types
Copyright : © 2019-2021 Albert Krewinkel
@@ -9,60 +10,33 @@
Pandoc data type constructors.
-}
module Text.Pandoc.Lua.Module.Types
- ( pushModule
+ ( documentedModule
) where
-import Data.Version (Version)
-import Foreign.Lua (Lua, NumResults)
-import Text.Pandoc.Definition
-import Text.Pandoc.Lua.Marshaling.AST (LuaAttr, LuaListAttributes)
-import Text.Pandoc.Lua.Marshaling.Version ()
-import Text.Pandoc.Lua.Util (addFunction)
-
-import qualified Foreign.Lua as Lua
-
--- | Push the pandoc.system module on the Lua stack.
-pushModule :: Lua NumResults
-pushModule = do
- Lua.newtable
- addFunction "Version" (return :: Version -> Lua Version)
- pushCloneTable
- Lua.setfield (Lua.nthFromTop 2) "clone"
- return 1
-
-pushCloneTable :: Lua NumResults
-pushCloneTable = do
- Lua.newtable
- addFunction "Attr" cloneAttr
- addFunction "Block" cloneBlock
- addFunction "Citation" cloneCitation
- addFunction "Inline" cloneInline
- addFunction "Meta" cloneMeta
- addFunction "MetaValue" cloneMetaValue
- addFunction "ListAttributes" cloneListAttributes
- addFunction "Pandoc" clonePandoc
- return 1
-
-cloneAttr :: LuaAttr -> Lua LuaAttr
-cloneAttr = return
-
-cloneBlock :: Block -> Lua Block
-cloneBlock = return
-
-cloneCitation :: Citation -> Lua Citation
-cloneCitation = return
-
-cloneInline :: Inline -> Lua Inline
-cloneInline = return
-
-cloneListAttributes :: LuaListAttributes -> Lua LuaListAttributes
-cloneListAttributes = return
-
-cloneMeta :: Meta -> Lua Meta
-cloneMeta = return
-
-cloneMetaValue :: MetaValue -> Lua MetaValue
-cloneMetaValue = return
-
-clonePandoc :: Pandoc -> Lua Pandoc
-clonePandoc = return
+import HsLua ( Module (..), (###), (<#>), (=#>)
+ , defun, functionResult, parameter)
+import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.ErrorConversion ()
+
+-- | Push the pandoc.types module on the Lua stack.
+documentedModule :: Module PandocError
+documentedModule = Module
+ { moduleName = "pandoc.types"
+ , moduleDescription =
+ "Constructors for types that are not part of the pandoc AST."
+ , moduleFields = []
+ , moduleFunctions =
+ [ defun "Version"
+ ### return
+ <#> parameter peekVersionFuzzy "string|integer|{integer,...}|Version"
+ "version_specifier"
+ (mconcat [ "either a version string like `'2.7.3'`, "
+ , "a single integer like `2`, "
+ , "list of integers like `{2,7,3}`, "
+ , "or a Version object"
+ ])
+ =#> functionResult pushVersion "Version" "A new Version object."
+ ]
+ , moduleOperations = []
+ }
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 3ec3afc26..02307cf7a 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -1,5 +1,7 @@
-{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Module.Utils
Copyright : Copyright © 2017-2021 Albert Krewinkel
@@ -11,143 +13,194 @@
Utility module for Lua, exposing internal helper functions.
-}
module Text.Pandoc.Lua.Module.Utils
- ( pushModule
+ ( documentedModule
+ , sha1
) where
import Control.Applicative ((<|>))
-import Control.Monad.Catch (try)
+import Control.Monad ((<$!>))
import Data.Data (showConstr, toConstr)
import Data.Default (def)
+import Data.Maybe (fromMaybe)
import Data.Version (Version)
-import Foreign.Lua (Peekable, Lua, NumResults (..))
+import HsLua as Lua
+import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
+import Text.Pandoc.Citeproc (getReferences)
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError)
-import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Marshaling.SimpleTable
- ( SimpleTable (..)
- , pushSimpleTable
- )
-import Text.Pandoc.Lua.PandocLua (PandocLua, addFunction, liftPandocLua)
+import Text.Pandoc.Lua.Marshal.AST
+import Text.Pandoc.Lua.Marshal.Reference
+import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))
import qualified Data.Digest.Pure.SHA as SHA
import qualified Data.ByteString.Lazy as BSL
+import qualified Data.Map as Map
import qualified Data.Text as T
-import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.Builder as B
import qualified Text.Pandoc.Filter.JSON as JSONFilter
import qualified Text.Pandoc.Shared as Shared
+import qualified Text.Pandoc.UTF8 as UTF8
import qualified Text.Pandoc.Writers.Shared as Shared
-- | Push the "pandoc.utils" module to the Lua stack.
-pushModule :: PandocLua NumResults
-pushModule = do
- liftPandocLua Lua.newtable
- addFunction "blocks_to_inlines" blocksToInlines
- addFunction "equals" equals
- addFunction "from_simple_table" from_simple_table
- addFunction "make_sections" makeSections
- addFunction "normalize_date" normalizeDate
- addFunction "run_json_filter" runJSONFilter
- addFunction "sha1" sha1
- addFunction "stringify" stringify
- addFunction "to_roman_numeral" toRomanNumeral
- addFunction "to_simple_table" to_simple_table
- addFunction "Version" (return :: Version -> Lua Version)
- return 1
-
--- | Squashes a list of blocks into inlines.
-blocksToInlines :: [Block] -> Lua.Optional [Inline] -> PandocLua [Inline]
-blocksToInlines blks optSep = liftPandocLua $ do
- let sep = maybe Shared.defaultBlocksSeparator B.fromList
- $ Lua.fromOptional optSep
- return $ B.toList (Shared.blocksToInlinesWithSep sep blks)
-
--- | Convert list of Pandoc blocks into sections using Divs.
-makeSections :: Bool -> Lua.Optional Int -> [Block] -> Lua [Block]
-makeSections number baselevel =
- return . Shared.makeSections number (Lua.fromOptional baselevel)
-
--- | Parse a date and convert (if possible) to "YYYY-MM-DD" format. We
--- limit years to the range 1601-9999 (ISO 8601 accepts greater than
--- or equal to 1583, but MS Word only accepts dates starting 1601).
--- Returns nil instead of a string if the conversion failed.
-normalizeDate :: T.Text -> Lua (Lua.Optional T.Text)
-normalizeDate = return . Lua.Optional . Shared.normalizeDate
-
--- | Run a JSON filter on the given document.
-runJSONFilter :: Pandoc
- -> FilePath
- -> Lua.Optional [String]
- -> PandocLua Pandoc
-runJSONFilter doc filterFile optArgs = do
- args <- case Lua.fromOptional optArgs of
- Just x -> return x
- Nothing -> liftPandocLua $ do
- Lua.getglobal "FORMAT"
- (:[]) <$> Lua.popValue
- JSONFilter.apply def args filterFile doc
-
--- | Calculate the hash of the given contents.
-sha1 :: BSL.ByteString
- -> Lua T.Text
-sha1 = return . T.pack . SHA.showDigest . SHA.sha1
+documentedModule :: Module PandocError
+documentedModule = Module
+ { moduleName = "pandoc.utils"
+ , moduleDescription = "pandoc utility functions"
+ , moduleFields = []
+ , moduleOperations = []
+ , moduleFunctions =
+ [ defun "blocks_to_inlines"
+ ### (\blks mSep -> do
+ let sep = maybe Shared.defaultBlocksSeparator B.fromList mSep
+ return $ B.toList (Shared.blocksToInlinesWithSep sep blks))
+ <#> parameter (peekList peekBlock) "list of blocks"
+ "blocks" ""
+ <#> optionalParameter (peekList peekInline) "list of inlines"
+ "inline" ""
+ =#> functionResult pushInlines "list of inlines" ""
+
+ , defun "equals"
+ ### equal
+ <#> parameter pure "AST element" "elem1" ""
+ <#> parameter pure "AST element" "elem2" ""
+ =#> functionResult pushBool "boolean" "true iff elem1 == elem2"
+
+ , defun "make_sections"
+ ### liftPure3 Shared.makeSections
+ <#> parameter peekBool "boolean" "numbering" "add header numbers"
+ <#> parameter (\i -> (Nothing <$ peekNil i) <|> (Just <$!> peekIntegral i))
+ "integer or nil" "baselevel" ""
+ <#> parameter (peekList peekBlock) "list of blocks"
+ "blocks" "document blocks to process"
+ =#> functionResult pushBlocks "list of Blocks"
+ "processes blocks"
+
+ , defun "normalize_date"
+ ### liftPure Shared.normalizeDate
+ <#> parameter peekText "string" "date" "the date string"
+ =#> functionResult (maybe pushnil pushText) "string or nil"
+ "normalized date, or nil if normalization failed."
+ #? T.unwords
+ [ "Parse a date and convert (if possible) to \"YYYY-MM-DD\" format. We"
+ , "limit years to the range 1601-9999 (ISO 8601 accepts greater than"
+ , "or equal to 1583, but MS Word only accepts dates starting 1601)."
+ , "Returns nil instead of a string if the conversion failed."
+ ]
+
+ , sha1
+
+ , defun "Version"
+ ### liftPure (id @Version)
+ <#> parameter peekVersionFuzzy
+ "version string, list of integers, or integer"
+ "v" "version description"
+ =#> functionResult pushVersion "Version" "new Version object"
+ #? "Creates a Version object."
+
+ , defun "references"
+ ### (unPandocLua . getReferences Nothing)
+ <#> parameter peekPandoc "Pandoc" "doc" "document"
+ =#> functionResult (pushPandocList pushReference) "table"
+ "lift of references"
+ #? mconcat
+ [ "Get references defined inline in the metadata and via an external "
+ , "bibliography. Only references that are actually cited in the "
+ , "document (either with a genuine citation or with `nocite`) are "
+ , "returned. URL variables are converted to links."
+ ]
+
+ , defun "run_json_filter"
+ ### (\doc filterPath margs -> do
+ args <- case margs of
+ Just xs -> return xs
+ Nothing -> do
+ Lua.getglobal "FORMAT"
+ (forcePeek ((:[]) <$!> peekString top) <* pop 1)
+ JSONFilter.apply def args filterPath doc
+ )
+ <#> parameter peekPandoc "Pandoc" "doc" "input document"
+ <#> parameter peekString "filepath" "filter_path" "path to filter"
+ <#> optionalParameter (peekList peekString) "list of strings"
+ "args" "arguments to pass to the filter"
+ =#> functionResult pushPandoc "Pandoc" "filtered document"
+
+ , defun "stringify"
+ ### stringify
+ <#> parameter pure "AST element" "elem" "some pandoc AST element"
+ =#> functionResult pushText "string" "stringified element"
+
+ , defun "from_simple_table"
+ ### from_simple_table
+ <#> parameter peekSimpleTable "SimpleTable" "simple_tbl" ""
+ =?> "Simple table"
+
+ , defun "to_roman_numeral"
+ ### liftPure Shared.toRomanNumeral
+ <#> parameter (peekIntegral @Int) "integer" "n" "number smaller than 4000"
+ =#> functionResult pushText "string" "roman numeral"
+ #? "Converts a number < 4000 to uppercase roman numeral."
+
+ , defun "to_simple_table"
+ ### to_simple_table
+ <#> parameter peekTable "Block" "tbl" "a table"
+ =#> functionResult pushSimpleTable "SimpleTable" "SimpleTable object"
+ #? "Converts a table into an old/simple table."
+
+ , defun "type"
+ ### (\idx -> getmetafield idx "__name" >>= \case
+ TypeString -> fromMaybe mempty <$> tostring top
+ _ -> ltype idx >>= typename)
+ <#> parameter pure "any" "object" ""
+ =#> functionResult pushByteString "string" "type of the given value"
+ #? ("Pandoc-friendly version of Lua's default `type` function, " <>
+ "returning the type of a value. If the argument has a " <>
+ "string-valued metafield `__name`, then it gives that string. " <>
+ "Otherwise it behaves just like the normal `type` function.")
+ ]
+ }
+
+-- | Documented Lua function to compute the hash of a string.
+sha1 :: DocumentedFunction e
+sha1 = defun "sha1"
+ ### liftPure (SHA.showDigest . SHA.sha1)
+ <#> parameter (fmap BSL.fromStrict . peekByteString) "string" "input" ""
+ =#> functionResult pushString "string" "hexadecimal hash value"
+ #? "Compute the hash of the given string value."
+
-- | Convert pandoc structure to a string with formatting removed.
-- Footnotes are skipped (since we don't want their contents in link
-- labels).
-stringify :: AstElement -> PandocLua T.Text
-stringify el = return $ case el of
- PandocElement pd -> Shared.stringify pd
- InlineElement i -> Shared.stringify i
- BlockElement b -> Shared.stringify b
- MetaElement m -> Shared.stringify m
- CitationElement c -> Shared.stringify c
- MetaValueElement m -> stringifyMetaValue m
- _ -> mempty
-
-stringifyMetaValue :: MetaValue -> T.Text
-stringifyMetaValue mv = case mv of
- MetaBool b -> T.toLower $ T.pack (show b)
- MetaString s -> s
- _ -> Shared.stringify mv
-
-equals :: AstElement -> AstElement -> PandocLua Bool
-equals e1 e2 = return (e1 == e2)
-
-data AstElement
- = PandocElement Pandoc
- | MetaElement Meta
- | BlockElement Block
- | InlineElement Inline
- | MetaValueElement MetaValue
- | AttrElement Attr
- | ListAttributesElement ListAttributes
- | CitationElement Citation
- deriving (Eq, Show)
-
-instance Peekable AstElement where
- peek idx = do
- res <- try $ (PandocElement <$> Lua.peek idx)
- <|> (InlineElement <$> Lua.peek idx)
- <|> (BlockElement <$> Lua.peek idx)
- <|> (AttrElement <$> Lua.peek idx)
- <|> (ListAttributesElement <$> Lua.peek idx)
- <|> (MetaElement <$> Lua.peek idx)
- <|> (MetaValueElement <$> Lua.peek idx)
- case res of
- Right x -> return x
- Left (_ :: PandocError) -> Lua.throwMessage
- "Expected an AST element, but could not parse value as such."
+stringify :: LuaError e => StackIndex -> LuaE e T.Text
+stringify idx = forcePeek . retrieving "stringifyable element" $
+ choice
+ [ (fmap Shared.stringify . peekPandoc)
+ , (fmap Shared.stringify . peekInline)
+ , (fmap Shared.stringify . peekBlock)
+ , (fmap Shared.stringify . peekCitation)
+ , (fmap stringifyMetaValue . peekMetaValue)
+ , (fmap (const "") . peekAttr)
+ , (fmap (const "") . peekListAttributes)
+ ] idx
+ where
+ stringifyMetaValue :: MetaValue -> T.Text
+ stringifyMetaValue mv = case mv of
+ MetaBool b -> T.toLower $ T.pack (show b)
+ MetaString s -> s
+ MetaList xs -> mconcat $ map stringifyMetaValue xs
+ MetaMap m -> mconcat $ map (stringifyMetaValue . snd) (Map.toList m)
+ _ -> Shared.stringify mv
-- | Converts an old/simple table into a normal table block element.
-from_simple_table :: SimpleTable -> Lua NumResults
+from_simple_table :: SimpleTable -> LuaE PandocError NumResults
from_simple_table (SimpleTable capt aligns widths head' body) = do
Lua.push $ Table
nullAttr
- (Caption Nothing [Plain capt])
+ (Caption Nothing [Plain capt | not (null capt)])
(zipWith (\a w -> (a, toColWidth w)) aligns widths)
(TableHead nullAttr [blockListToRow head' | not (null head') ])
- [TableBody nullAttr 0 [] $ map blockListToRow body]
+ [TableBody nullAttr 0 [] $ map blockListToRow body | not (null body)]
(TableFoot nullAttr [])
return (NumResults 1)
where
@@ -159,17 +212,19 @@ from_simple_table (SimpleTable capt aligns widths head' body) = do
toColWidth w = ColWidth w
-- | Converts a table into an old/simple table.
-to_simple_table :: Block -> Lua NumResults
+to_simple_table :: Block -> LuaE PandocError SimpleTable
to_simple_table = \case
Table _attr caption specs thead tbodies tfoot -> do
let (capt, aligns, widths, headers, rows) =
Shared.toLegacyTable caption specs thead tbodies tfoot
- pushSimpleTable $ SimpleTable capt aligns widths headers rows
- return (NumResults 1)
- blk ->
- Lua.throwMessage $
- "Expected Table, got " <> showConstr (toConstr blk) <> "."
-
--- | Convert a number < 4000 to uppercase roman numeral.
-toRomanNumeral :: Lua.Integer -> PandocLua T.Text
-toRomanNumeral = return . Shared.toRomanNumeral . fromIntegral
+ return $ SimpleTable capt aligns widths headers rows
+ blk -> Lua.failLua $ mconcat
+ [ "Expected Table, got ", showConstr (toConstr blk), "." ]
+
+peekTable :: LuaError e => Peeker e Block
+peekTable idx = peekBlock idx >>= \case
+ t@(Table {}) -> return t
+ b -> Lua.failPeek $ mconcat
+ [ "Expected Table, got "
+ , UTF8.fromString $ showConstr (toConstr b)
+ , "." ]
diff --git a/src/Text/Pandoc/Lua/Orphans.hs b/src/Text/Pandoc/Lua/Orphans.hs
new file mode 100644
index 000000000..d5b8f2c5d
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Orphans.hs
@@ -0,0 +1,116 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# LANGUAGE FlexibleInstances #-}
+{- |
+ Module : Text.Pandoc.Lua.Orphans
+ Copyright : © 2012-2021 John MacFarlane
+ © 2017-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Orphan instances for Lua's Pushable and Peekable type classes.
+-}
+module Text.Pandoc.Lua.Orphans () where
+
+import Data.Version (Version)
+import HsLua
+import HsLua.Module.Version (peekVersionFuzzy)
+import Text.Pandoc.Definition
+import Text.Pandoc.Lua.Marshal.AST
+import Text.Pandoc.Lua.Marshal.CommonState ()
+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
+ push = pushPandoc
+
+instance Pushable Meta where
+ push = pushMeta
+
+instance Pushable MetaValue where
+ push = pushMetaValue
+
+instance Pushable Block where
+ push = pushBlock
+
+instance {-# OVERLAPPING #-} Pushable [Block] where
+ push = pushBlocks
+
+instance Pushable Alignment where
+ push = pushString . show
+
+instance Pushable CitationMode where
+ push = pushCitationMode
+
+instance Pushable Format where
+ push = pushFormat
+
+instance Pushable ListNumberDelim where
+ push = pushString . show
+
+instance Pushable ListNumberStyle where
+ push = pushString . show
+
+instance Pushable MathType where
+ push = pushMathType
+
+instance Pushable QuoteType where
+ push = pushQuoteType
+
+instance Pushable Cell where
+ push = pushCell
+
+instance Peekable Cell where
+ peek = forcePeek . peekCell
+
+instance Pushable Inline where
+ push = pushInline
+
+instance {-# OVERLAPPING #-} Pushable [Inline] where
+ push = pushInlines
+
+instance Pushable Citation where
+ push = pushCitation
+
+instance Pushable Row where
+ push = pushRow
+
+instance Pushable TableBody where
+ push = pushTableBody
+
+instance Pushable TableFoot where
+ push = pushTableFoot
+
+instance Pushable TableHead where
+ push = pushTableHead
+
+-- These instances exist only for testing. It's a hack to avoid making
+-- the marshalling modules public.
+instance Peekable Inline where
+ peek = forcePeek . peekInline
+
+instance Peekable Block where
+ peek = forcePeek . peekBlock
+
+instance Peekable Meta where
+ peek = forcePeek . peekMeta
+
+instance Peekable Pandoc where
+ peek = forcePeek . peekPandoc
+
+instance Peekable Row where
+ peek = forcePeek . peekRow
+
+instance Peekable Version where
+ peek = forcePeek . peekVersionFuzzy
+
+instance {-# OVERLAPPING #-} Peekable Attr where
+ peek = forcePeek . peekAttr
+
+instance Pushable Sources where
+ push = pushSources
diff --git a/src/Text/Pandoc/Lua/Packages.hs b/src/Text/Pandoc/Lua/Packages.hs
index 2f1c139db..c36c3c670 100644
--- a/src/Text/Pandoc/Lua/Packages.hs
+++ b/src/Text/Pandoc/Lua/Packages.hs
@@ -1,3 +1,6 @@
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Packages
Copyright : Copyright © 2017-2021 Albert Krewinkel
@@ -13,12 +16,13 @@ module Text.Pandoc.Lua.Packages
) where
import Control.Monad (forM_)
-import Foreign.Lua (NumResults)
-import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, loadDefaultModule)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.Marshal.List (pushListModule)
+import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua)
-import qualified Foreign.Lua as Lua
-import qualified Foreign.Lua.Module.Path as Path
-import qualified Foreign.Lua.Module.Text as Text
+import qualified HsLua as Lua
+import qualified HsLua.Module.Path as Path
+import qualified HsLua.Module.Text as Text
import qualified Text.Pandoc.Lua.Module.Pandoc as Pandoc
import qualified Text.Pandoc.Lua.Module.MediaBag as MediaBag
import qualified Text.Pandoc.Lua.Module.System as System
@@ -30,8 +34,8 @@ installPandocPackageSearcher :: PandocLua ()
installPandocPackageSearcher = liftPandocLua $ do
Lua.getglobal' "package.searchers"
shiftArray
- Lua.pushHaskellFunction pandocPackageSearcher
- Lua.rawseti (Lua.nthFromTop 2) 1
+ Lua.pushHaskellFunction $ Lua.toHaskellFunction pandocPackageSearcher
+ Lua.rawseti (Lua.nth 2) 1
Lua.pop 1 -- remove 'package.searchers' from stack
where
shiftArray = forM_ [4, 3, 2, 1] $ \i -> do
@@ -39,22 +43,27 @@ installPandocPackageSearcher = liftPandocLua $ do
Lua.rawseti (-2) (i + 1)
-- | Load a pandoc module.
-pandocPackageSearcher :: String -> PandocLua NumResults
+pandocPackageSearcher :: String -> PandocLua Lua.NumResults
pandocPackageSearcher pkgName =
case pkgName of
- "pandoc" -> pushWrappedHsFun Pandoc.pushModule
- "pandoc.mediabag" -> pushWrappedHsFun MediaBag.pushModule
- "pandoc.path" -> pushWrappedHsFun Path.pushModule
- "pandoc.system" -> pushWrappedHsFun System.pushModule
- "pandoc.types" -> pushWrappedHsFun Types.pushModule
- "pandoc.utils" -> pushWrappedHsFun Utils.pushModule
- "text" -> pushWrappedHsFun Text.pushModule
- "pandoc.List" -> pushWrappedHsFun (loadDefaultModule pkgName)
+ "pandoc" -> pushModuleLoader Pandoc.documentedModule
+ "pandoc.mediabag" -> pushModuleLoader MediaBag.documentedModule
+ "pandoc.path" -> pushModuleLoader Path.documentedModule
+ "pandoc.system" -> pushModuleLoader System.documentedModule
+ "pandoc.types" -> pushModuleLoader Types.documentedModule
+ "pandoc.utils" -> pushModuleLoader Utils.documentedModule
+ "text" -> pushModuleLoader Text.documentedModule
+ "pandoc.List" -> pushWrappedHsFun . Lua.toHaskellFunction @PandocError $
+ (Lua.NumResults 1 <$ pushListModule @PandocError)
_ -> reportPandocSearcherFailure
where
+ pushModuleLoader mdl = liftPandocLua $ do
+ Lua.pushHaskellFunction $
+ Lua.NumResults 1 <$ Lua.pushModule @PandocError mdl
+ return (Lua.NumResults 1)
pushWrappedHsFun f = liftPandocLua $ do
Lua.pushHaskellFunction f
return 1
reportPandocSearcherFailure = liftPandocLua $ do
- Lua.push ("\n\t" <> pkgName <> "is not one of pandoc's default packages")
- return (1 :: NumResults)
+ Lua.push ("\n\t" <> pkgName <> " is not one of pandoc's default packages")
+ return (Lua.NumResults 1)
diff --git a/src/Text/Pandoc/Lua/PandocLua.hs b/src/Text/Pandoc/Lua/PandocLua.hs
index 750e019b6..71fdf8d5c 100644
--- a/src/Text/Pandoc/Lua/PandocLua.hs
+++ b/src/Text/Pandoc/Lua/PandocLua.hs
@@ -22,27 +22,22 @@ module Text.Pandoc.Lua.PandocLua
( PandocLua (..)
, runPandocLua
, liftPandocLua
- , addFunction
- , loadDefaultModule
) where
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 Control.Monad.IO.Class (MonadIO)
+import HsLua as Lua
+import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
+import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
-import Text.Pandoc.Lua.ErrorConversion (errorConversion)
+import Text.Pandoc.Lua.Marshal.CommonState (peekCommonState)
import qualified Control.Monad.Catch as Catch
-import qualified Data.Text as T
-import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.Class.IO as IO
-- | Type providing access to both, pandoc and Lua operations.
-newtype PandocLua a = PandocLua { unPandocLua :: Lua a }
+newtype PandocLua a = PandocLua { unPandocLua :: LuaE PandocError a }
deriving
( Applicative
, Functor
@@ -54,16 +49,16 @@ newtype PandocLua a = PandocLua { unPandocLua :: Lua a }
)
-- | Lift a @'Lua'@ operation into the @'PandocLua'@ type.
-liftPandocLua :: Lua a -> PandocLua a
+liftPandocLua :: LuaE PandocError a -> PandocLua a
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
- (result, newState) <- liftIO . Lua.run' errorConversion . unPandocLua $ do
+ (result, newState) <- liftIO . Lua.run . unPandocLua $ do
putCommonState origState
liftPandocLua $ setGlobals globals
r <- pLua
@@ -72,38 +67,14 @@ runPandocLua pLua = do
putCommonState newState
return result
-instance {-# OVERLAPPING #-} ToHaskellFunction (PandocLua NumResults) where
- toHsFun _narg = unPandocLua
-
-instance Pushable a => ToHaskellFunction (PandocLua a) where
- toHsFun _narg x = 1 <$ (unPandocLua x >>= Lua.push)
-
--- | Add a function to the table at the top of the stack, using the given name.
-addFunction :: ToHaskellFunction a => String -> a -> PandocLua ()
-addFunction name fn = liftPandocLua $ do
- Lua.push name
- Lua.pushHaskellFunction fn
- Lua.rawset (-3)
-
--- | Load a pure Lua module included with pandoc. Leaves the result on
--- the stack and returns @NumResults 1@.
---
--- The script is loaded from the default data directory. We do not load
--- from data directories supplied via command line, as this could cause
--- scripts to be executed even though they had not been passed explicitly.
-loadDefaultModule :: String -> PandocLua NumResults
-loadDefaultModule name = do
- script <- readDefaultDataFile (name <> ".lua")
- status <- liftPandocLua $ Lua.dostring script
- if status == Lua.OK
- then return (1 :: NumResults)
- else do
- msg <- liftPandocLua Lua.popValue
- let err = "Error while loading `" <> name <> "`.\n" <> msg
- throwError $ PandocLuaError (T.pack err)
+instance {-# OVERLAPPING #-} Exposable PandocError (PandocLua NumResults) where
+ partialApply _narg = unPandocLua
+
+instance Pushable a => Exposable PandocError (PandocLua a) where
+ partialApply _narg x = 1 <$ (unPandocLua x >>= Lua.push)
-- | Global variables which should always be set.
-defaultGlobals :: PandocIO [Global]
+defaultGlobals :: PandocMonad m => m [Global]
defaultGlobals = do
commonState <- getCommonState
return
@@ -127,6 +98,7 @@ instance PandocMonad PandocLua where
readFileLazy = IO.readFileLazy
readFileStrict = IO.readFileStrict
+ readStdinStrict = IO.readStdinStrict
glob = IO.glob
fileExists = IO.fileExists
@@ -135,7 +107,7 @@ instance PandocMonad PandocLua where
getCommonState = PandocLua $ do
Lua.getglobal "PANDOC_STATE"
- Lua.peek Lua.stackTop
+ forcePeek $ peekCommonState Lua.top
putCommonState = PandocLua . setGlobals . (:[]) . PANDOC_STATE
logOutput = IO.logOutput
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index 70a8a6d47..9c6f42b2b 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -1,6 +1,4 @@
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE LambdaCase #-}
-{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Util
Copyright : © 2012-2021 John MacFarlane,
@@ -13,115 +11,34 @@
Lua utility functions.
-}
module Text.Pandoc.Lua.Util
- ( getTag
- , rawField
- , addField
- , addFunction
- , addValue
- , pushViaConstructor
- , defineHowTo
- , throwTopMessageAsError'
+ ( addField
, callWithTraceback
+ , pcallWithTraceback
, dofileWithTraceback
) where
-import Control.Monad (unless, when)
-import Data.Text (Text)
-import Foreign.Lua ( Lua, NumArgs, NumResults, Peekable, Pushable, StackIndex
- , Status, ToHaskellFunction )
-import qualified Foreign.Lua as Lua
-import qualified Text.Pandoc.UTF8 as UTF8
-
--- | Get value behind key from table at given index.
-rawField :: Peekable a => StackIndex -> String -> Lua a
-rawField idx key = do
- absidx <- Lua.absindex idx
- Lua.push key
- Lua.rawget absidx
- Lua.popValue
+import Control.Monad (when)
+import HsLua
+import qualified HsLua as Lua
-- | Add a value to the table at the top of the stack at a string-index.
-addField :: Pushable a => String -> a -> Lua ()
-addField = addValue
-
--- | Add a key-value pair to the table at the top of the stack.
-addValue :: (Pushable a, Pushable b) => a -> b -> Lua ()
-addValue key value = do
+addField :: (LuaError e, Pushable a) => String -> a -> LuaE e ()
+addField key value = do
Lua.push key
Lua.push value
- Lua.rawset (Lua.nthFromTop 3)
-
--- | Add a function to the table at the top of the stack, using the given name.
-addFunction :: ToHaskellFunction a => String -> a -> Lua ()
-addFunction name fn = do
- Lua.push name
- Lua.pushHaskellFunction fn
- Lua.rawset (-3)
-
--- | Helper class for pushing a single value to the stack via a lua function.
--- See @pushViaCall@.
-class PushViaCall a where
- pushViaCall' :: String -> Lua () -> NumArgs -> a
-
-instance PushViaCall (Lua ()) where
- pushViaCall' fn pushArgs num = do
- Lua.push fn
- Lua.rawget Lua.registryindex
- pushArgs
- Lua.call num 1
-
-instance (Pushable a, PushViaCall b) => PushViaCall (a -> b) where
- pushViaCall' fn pushArgs num x =
- pushViaCall' fn (pushArgs *> Lua.push x) (num + 1)
-
--- | Push an value to the stack via a lua function. The lua function is called
--- with all arguments that are passed to this function and is expected to return
--- a single value.
-pushViaCall :: PushViaCall a => String -> a
-pushViaCall fn = pushViaCall' fn (return ()) 0
-
--- | Call a pandoc element constructor within Lua, passing all given arguments.
-pushViaConstructor :: PushViaCall a => String -> a
-pushViaConstructor pandocFn = pushViaCall ("pandoc." ++ pandocFn)
-
--- | Get the tag of a value. This is an optimized and specialized version of
--- @Lua.getfield idx "tag"@. It only checks for the field on the table at index
--- @idx@ and on its metatable, also ignoring any @__index@ value on the
--- metatable.
-getTag :: StackIndex -> Lua String
-getTag idx = do
- -- push metatable or just the table
- Lua.getmetatable idx >>= \hasMT -> unless hasMT (Lua.pushvalue idx)
- Lua.push ("tag" :: Text)
- Lua.rawget (Lua.nthFromTop 2)
- Lua.tostring Lua.stackTop <* Lua.pop 2 >>= \case
- Nothing -> Lua.throwMessage "untagged value"
- Just x -> return (UTF8.toString x)
-
--- | Modify the message at the top of the stack before throwing it as an
--- Exception.
-throwTopMessageAsError' :: (String -> String) -> Lua a
-throwTopMessageAsError' modifier = do
- msg <- Lua.tostring' Lua.stackTop
- Lua.pop 2 -- remove error and error string pushed by tostring'
- Lua.throwMessage (modifier (UTF8.toString msg))
-
--- | Mark the context of a Lua computation for better error reporting.
-defineHowTo :: String -> Lua a -> Lua a
-defineHowTo ctx op = Lua.errorConversion >>= \ec ->
- Lua.addContextToException ec ("Could not " <> ctx <> ": ") op
+ Lua.rawset (Lua.nth 3)
-- | Like @'Lua.pcall'@, but uses a predefined error handler which adds a
-- traceback on error.
-pcallWithTraceback :: NumArgs -> NumResults -> Lua Status
+pcallWithTraceback :: LuaError e => NumArgs -> NumResults -> LuaE e Status
pcallWithTraceback nargs nresults = do
- let traceback' :: Lua NumResults
+ let traceback' :: LuaError e => LuaE e NumResults
traceback' = do
l <- Lua.state
- msg <- Lua.tostring' (Lua.nthFromBottom 1)
- Lua.traceback l (Just (UTF8.toString msg)) 2
+ msg <- Lua.tostring' (Lua.nthBottom 1)
+ Lua.traceback l (Just msg) 2
return 1
- tracebackIdx <- Lua.absindex (Lua.nthFromTop (Lua.fromNumArgs nargs + 1))
+ tracebackIdx <- Lua.absindex (Lua.nth (Lua.fromNumArgs nargs + 1))
Lua.pushHaskellFunction traceback'
Lua.insert tracebackIdx
result <- Lua.pcall nargs nresults (Just tracebackIdx)
@@ -129,15 +46,15 @@ pcallWithTraceback nargs nresults = do
return result
-- | Like @'Lua.call'@, but adds a traceback to the error message (if any).
-callWithTraceback :: NumArgs -> NumResults -> Lua ()
+callWithTraceback :: LuaError e => NumArgs -> NumResults -> LuaE e ()
callWithTraceback nargs nresults = do
result <- pcallWithTraceback nargs nresults
when (result /= Lua.OK)
- Lua.throwTopMessage
+ Lua.throwErrorAsException
-- | Run the given string as a Lua program, while also adding a traceback to the
-- error message if an error occurs.
-dofileWithTraceback :: FilePath -> Lua Status
+dofileWithTraceback :: LuaError e => FilePath -> LuaE e Status
dofileWithTraceback fp = do
loadRes <- Lua.loadfile fp
case loadRes of
diff --git a/src/Text/Pandoc/Lua/Walk.hs b/src/Text/Pandoc/Lua/Walk.hs
deleted file mode 100644
index d6d973496..000000000
--- a/src/Text/Pandoc/Lua/Walk.hs
+++ /dev/null
@@ -1,158 +0,0 @@
-{-# LANGUAGE DeriveTraversable #-}
-{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE MultiParamTypeClasses #-}
-{- |
-Module : Text.Pandoc.Lua.Walk
-Copyright : © 2012-2021 John MacFarlane,
- © 2017-2021 Albert Krewinkel
-License : GNU GPL, version 2 or above
-Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
-Stability : alpha
-
-Walking documents in a filter-suitable way.
--}
-module Text.Pandoc.Lua.Walk
- ( SingletonsList (..)
- )
-where
-
-import Control.Monad ((<=<))
-import Text.Pandoc.Definition
-import Text.Pandoc.Walk
-
--- | Helper type which allows to traverse trees in order, while splicing in
--- trees.
---
--- The only interesting use of this type is via it's '@Walkable@' instance. That
--- instance makes it possible to walk a Pandoc document (or a subset thereof),
--- while applying a function on each element of an AST element /list/, and have
--- the resulting list spliced back in place of the original element. This is the
--- traversal/splicing method used for Lua filters.
-newtype SingletonsList a = SingletonsList { singletonsList :: [a] }
- deriving (Functor, Foldable, Traversable)
-
---
--- SingletonsList Inline
---
-instance {-# OVERLAPPING #-} Walkable (SingletonsList Inline) [Inline] where
- walkM = walkSingletonsListM
- query = querySingletonsList
-
-instance Walkable (SingletonsList Inline) Pandoc where
- walkM = walkPandocM
- query = queryPandoc
-
-instance Walkable (SingletonsList Inline) Citation where
- walkM = walkCitationM
- query = queryCitation
-
-instance Walkable (SingletonsList Inline) Inline where
- walkM = walkInlineM
- query = queryInline
-
-instance Walkable (SingletonsList Inline) Block where
- walkM = walkBlockM
- query = queryBlock
-
-instance Walkable (SingletonsList Inline) Row where
- walkM = walkRowM
- query = queryRow
-
-instance Walkable (SingletonsList Inline) TableHead where
- walkM = walkTableHeadM
- query = queryTableHead
-
-instance Walkable (SingletonsList Inline) TableBody where
- walkM = walkTableBodyM
- query = queryTableBody
-
-instance Walkable (SingletonsList Inline) TableFoot where
- walkM = walkTableFootM
- query = queryTableFoot
-
-instance Walkable (SingletonsList Inline) Caption where
- walkM = walkCaptionM
- query = queryCaption
-
-instance Walkable (SingletonsList Inline) Cell where
- walkM = walkCellM
- query = queryCell
-
-instance Walkable (SingletonsList Inline) MetaValue where
- walkM = walkMetaValueM
- query = queryMetaValue
-
-instance Walkable (SingletonsList Inline) Meta where
- walkM f (Meta metamap) = Meta <$> walkM f metamap
- query f (Meta metamap) = query f metamap
-
---
--- SingletonsList Block
---
-instance {-# OVERLAPPING #-} Walkable (SingletonsList Block) [Block] where
- walkM = walkSingletonsListM
- query = querySingletonsList
-
-instance Walkable (SingletonsList Block) Pandoc where
- walkM = walkPandocM
- query = queryPandoc
-
-instance Walkable (SingletonsList Block) Citation where
- walkM = walkCitationM
- query = queryCitation
-
-instance Walkable (SingletonsList Block) Inline where
- walkM = walkInlineM
- query = queryInline
-
-instance Walkable (SingletonsList Block) Block where
- walkM = walkBlockM
- query = queryBlock
-
-instance Walkable (SingletonsList Block) Row where
- walkM = walkRowM
- query = queryRow
-
-instance Walkable (SingletonsList Block) TableHead where
- walkM = walkTableHeadM
- query = queryTableHead
-
-instance Walkable (SingletonsList Block) TableBody where
- walkM = walkTableBodyM
- query = queryTableBody
-
-instance Walkable (SingletonsList Block) TableFoot where
- walkM = walkTableFootM
- query = queryTableFoot
-
-instance Walkable (SingletonsList Block) Caption where
- walkM = walkCaptionM
- query = queryCaption
-
-instance Walkable (SingletonsList Block) Cell where
- walkM = walkCellM
- query = queryCell
-
-instance Walkable (SingletonsList Block) MetaValue where
- walkM = walkMetaValueM
- query = queryMetaValue
-
-instance Walkable (SingletonsList Block) Meta where
- walkM f (Meta metamap) = Meta <$> walkM f metamap
- query f (Meta metamap) = query f metamap
-
-
-walkSingletonsListM :: (Monad m, Walkable (SingletonsList a) a)
- => (SingletonsList a -> m (SingletonsList a))
- -> [a] -> m [a]
-walkSingletonsListM f =
- let f' = fmap singletonsList . f . SingletonsList . (:[]) <=< walkM f
- in fmap mconcat . mapM f'
-
-querySingletonsList :: (Monoid c, Walkable (SingletonsList a) a)
- => (SingletonsList a -> c)
- -> [a] -> c
-querySingletonsList f =
- let f' x = f (SingletonsList [x]) `mappend` query f x
- in mconcat . map f'