aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Module')
-rw-r--r--src/Text/Pandoc/Lua/Module/MediaBag.hs19
-rw-r--r--src/Text/Pandoc/Lua/Module/Pandoc.hs87
-rw-r--r--src/Text/Pandoc/Lua/Module/System.hs39
-rw-r--r--src/Text/Pandoc/Lua/Module/Types.hs66
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs227
5 files changed, 254 insertions, 184 deletions
diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs
index 3eed50fca..a1fc40732 100644
--- a/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -15,18 +15,19 @@ module Text.Pandoc.Lua.Module.MediaBag
import Prelude hiding (lookup)
import Control.Monad (zipWithM_)
-import Foreign.Lua (Lua, NumResults, Optional)
+import HsLua (LuaE, NumResults, Optional)
+import HsLua.Marshalling (pushIterator)
import Text.Pandoc.Class.CommonState (CommonState (..))
import Text.Pandoc.Class.PandocMonad (fetchItem, getMediaBag, modifyCommonState,
setMediaBag)
+import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Marshaling.MediaBag (pushIterator)
import Text.Pandoc.Lua.PandocLua (PandocLua (..), liftPandocLua, addFunction)
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
--
@@ -65,7 +66,15 @@ insert fp optionalMime contents = do
-- | Returns iterator values to be used with a Lua @for@ loop.
items :: PandocLua NumResults
-items = getMediaBag >>= liftPandocLua . pushIterator
+items = do
+ mb <- getMediaBag
+ liftPandocLua $ do
+ let pushItem (fp, mimetype, contents) = do
+ Lua.pushString fp
+ Lua.pushText mimetype
+ Lua.pushByteString $ BL.toStrict contents
+ return (Lua.NumResults 3)
+ pushIterator pushItem (MB.mediaItems mb)
lookup :: FilePath
-> PandocLua NumResults
@@ -86,7 +95,7 @@ list = do
zipWithM_ addEntry [1..] dirContents
return 1
where
- addEntry :: Lua.Integer -> (FilePath, MimeType, Int) -> Lua ()
+ addEntry :: Lua.Integer -> (FilePath, MimeType, Int) -> LuaE PandocError ()
addEntry idx (fp, mimeType, contentLength) = do
Lua.newtable
Lua.push ("path" :: T.Text) *> Lua.push fp *> Lua.rawset (-3)
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index 5c14b3a30..0a9ebaec5 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -15,29 +15,30 @@ module Text.Pandoc.Lua.Module.Pandoc
) where
import Prelude hiding (read)
-import Control.Monad (when)
+import Control.Monad ((>=>), when)
import Control.Monad.Except (throwError)
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
-import Foreign.Lua (Lua, NumResults, Optional, Peekable, Pushable)
+import HsLua as Lua 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,
+import Text.Pandoc.Lua.Filter (SingletonsList (..), walkInlines,
walkInlineLists, walkBlocks, walkBlockLists)
import Text.Pandoc.Lua.Marshaling ()
+import Text.Pandoc.Lua.Marshaling.AST
import Text.Pandoc.Lua.Marshaling.List (List (..))
import Text.Pandoc.Lua.PandocLua (PandocLua, addFunction, liftPandocLua,
loadDefaultModule)
-import Text.Pandoc.Walk (Walkable)
import Text.Pandoc.Options (ReaderOptions (readerExtensions))
import Text.Pandoc.Process (pipeProcess)
import Text.Pandoc.Readers (Reader (..), getReader)
+import Text.Pandoc.Walk (Walkable)
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
@@ -48,23 +49,25 @@ pushModule = do
loadDefaultModule "pandoc"
addFunction "read" read
addFunction "pipe" pipe
- addFunction "walk_block" walk_block
- addFunction "walk_inline" walk_inline
+ addFunction "walk_block" (walkElement peekBlock pushBlock)
+ addFunction "walk_inline" (walkElement peekInline pushInline)
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
+ => Peeker PandocError a -> Pusher PandocError a
+ -> LuaE PandocError NumResults
+walkElement peek' push' = do
+ x <- forcePeek $ peek' (nthBottom 1)
+ f <- peek (nthBottom 2)
+ let walk' = walkInlines f
+ >=> walkInlineLists f
+ >=> walkBlocks f
+ >=> walkBlockLists f
+ walk' x >>= push'
+ return (NumResults 1)
read :: T.Text -> Optional T.Text -> PandocLua NumResults
read content formatSpecOrNil = liftPandocLua $ do
@@ -93,7 +96,9 @@ 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)
+ ExitFailure n -> do
+ pushPipeError (PipeError (T.pack command) n output)
+ Lua.error
data PipeError = PipeError
{ pipeErrorCommand :: T.Text
@@ -101,29 +106,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)
+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)
-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
+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 :: PipeError -> Lua BL.ByteString
- pipeErrorMessage (PipeError cmd errorCode output) = return $ mconcat
+ 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 +141,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..8589f672c 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
@@ -12,22 +14,31 @@ module Text.Pandoc.Lua.Module.System
( pushModule
) 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 HsLua hiding (pushModule)
+import HsLua.Module.System
+ (arch, env, getwd, os, with_env, with_tmpdir, with_wd)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.ErrorConversion ()
-import qualified Foreign.Lua as Lua
+import qualified HsLua as Lua
-- | Push the pandoc.system module on the Lua stack.
-pushModule :: Lua NumResults
+pushModule :: LuaE PandocError 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
+ Lua.pushModule $ Module
+ { moduleName = "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 = []
+ }
return 1
diff --git a/src/Text/Pandoc/Lua/Module/Types.hs b/src/Text/Pandoc/Lua/Module/Types.hs
index bb4f02c3c..a9ce14ce7 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
@@ -13,56 +14,41 @@ module Text.Pandoc.Lua.Module.Types
) where
import Data.Version (Version)
-import Foreign.Lua (Lua, NumResults)
-import Text.Pandoc.Definition
-import Text.Pandoc.Lua.Marshaling.AST (LuaAttr, LuaListAttributes)
+import HsLua (LuaE, NumResults, Peeker, Pusher)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.ErrorConversion ()
+import Text.Pandoc.Lua.Marshaling.AST
import Text.Pandoc.Lua.Marshaling.Version ()
import Text.Pandoc.Lua.Util (addFunction)
-import qualified Foreign.Lua as Lua
+import qualified HsLua as Lua
--- | Push the pandoc.system module on the Lua stack.
-pushModule :: Lua NumResults
+-- | Push the pandoc.types module on the Lua stack.
+pushModule :: LuaE PandocError NumResults
pushModule = do
Lua.newtable
- addFunction "Version" (return :: Version -> Lua Version)
+ addFunction "Version" (return :: Version -> LuaE PandocError Version)
pushCloneTable
- Lua.setfield (Lua.nthFromTop 2) "clone"
+ Lua.setfield (Lua.nth 2) "clone"
return 1
-pushCloneTable :: Lua NumResults
+pushCloneTable :: LuaE PandocError 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
+ addFunction "Attr" $ cloneWith peekAttr pushAttr
+ addFunction "Block" $ cloneWith peekBlock pushBlock
+ addFunction "Citation" $ cloneWith peekCitation Lua.push
+ addFunction "Inline" $ cloneWith peekInline pushInline
+ addFunction "Meta" $ cloneWith peekMeta Lua.push
+ addFunction "MetaValue" $ cloneWith peekMetaValue pushMetaValue
+ addFunction "ListAttributes" $ cloneWith peekListAttributes pushListAttributes
+ addFunction "Pandoc" $ cloneWith peekPandoc pushPandoc
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
+cloneWith :: Peeker PandocError a
+ -> Pusher PandocError a
+ -> LuaE PandocError NumResults
+cloneWith peeker pusher = do
+ x <- Lua.forcePeek $ peeker (Lua.nthBottom 1)
+ pusher x
+ return (Lua.NumResults 1)
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 3ec3afc26..8b6e31b43 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
@@ -15,82 +17,137 @@ module Text.Pandoc.Lua.Module.Utils
) where
import Control.Applicative ((<|>))
-import Control.Monad.Catch (try)
+import Control.Monad ((<$!>))
import Data.Data (showConstr, toConstr)
import Data.Default (def)
import Data.Version (Version)
-import Foreign.Lua (Peekable, Lua, NumResults (..))
+import HsLua as Lua hiding (pushModule)
+import HsLua.Class.Peekable (PeekError)
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshaling ()
+import Text.Pandoc.Lua.Marshaling.AST
+ ( peekBlock, peekInline, peekPandoc, pushBlock, pushInline, pushPandoc
+ , peekAttr, peekListAttributes, peekMeta, peekMetaValue)
+import Text.Pandoc.Lua.Marshaling.List (pushPandocList)
import Text.Pandoc.Lua.Marshaling.SimpleTable
- ( SimpleTable (..)
- , pushSimpleTable
- )
-import Text.Pandoc.Lua.PandocLua (PandocLua, addFunction, liftPandocLua)
+ ( SimpleTable (..), peekSimpleTable, pushSimpleTable )
+import Text.Pandoc.Lua.Marshaling.Version (peekVersionFuzzy, pushVersion)
+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.Text as T
-import qualified Foreign.Lua as Lua
+import qualified HsLua.Packaging 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
+pandocUtilsModule :: Module PandocError
+pandocUtilsModule = 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 (pushPandocList pushInline) "list of inlines" ""
+
+ , defun "equals"
+ ### liftPure2 (==)
+ <#> parameter peekAstElement "AST element" "elem1" ""
+ <#> parameter peekAstElement "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 (pushPandocList pushBlock) "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."
+ ]
+
+ , 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."
+
+ , 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 "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"
+ ### unPandocLua . stringify
+ <#> parameter peekAstElement "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."
+ ]
+ }
+
+pushModule :: LuaE PandocError NumResults
+pushModule = 1 <$ Lua.pushModule pandocUtilsModule
+
-- | Convert pandoc structure to a string with formatting removed.
-- Footnotes are skipped (since we don't want their contents in link
@@ -111,9 +168,6 @@ stringifyMetaValue mv = case mv of
MetaString s -> s
_ -> Shared.stringify mv
-equals :: AstElement -> AstElement -> PandocLua Bool
-equals e1 e2 = return (e1 == e2)
-
data AstElement
= PandocElement Pandoc
| MetaElement Meta
@@ -125,22 +179,19 @@ data AstElement
| 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."
+peekAstElement :: PeekError e => Peeker e AstElement
+peekAstElement = retrieving "pandoc AST element" . choice
+ [ (fmap PandocElement . peekPandoc)
+ , (fmap InlineElement . peekInline)
+ , (fmap BlockElement . peekBlock)
+ , (fmap AttrElement . peekAttr)
+ , (fmap ListAttributesElement . peekListAttributes)
+ , (fmap MetaElement . peekMeta)
+ , (fmap MetaValueElement . peekMetaValue)
+ ]
-- | 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
@@ -159,17 +210,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)
+ , "." ]