aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module/Utils.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Module/Utils.hs')
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs293
1 files changed, 174 insertions, 119 deletions
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)
+ , "." ]