diff options
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Utils.hs | 25 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/StackInstances.hs | 28 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Util.hs | 4 |
3 files changed, 54 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs index 3a3727355..35495dae1 100644 --- a/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/src/Text/Pandoc/Lua/Module/Utils.hs @@ -30,10 +30,10 @@ module Text.Pandoc.Lua.Module.Utils ) where import Control.Applicative ((<|>)) -import Foreign.Lua (FromLuaStack, Lua, NumResults) +import Foreign.Lua (FromLuaStack, Lua, LuaInteger, NumResults) import Text.Pandoc.Definition (Pandoc, Meta, Block, Inline) import Text.Pandoc.Lua.StackInstances () -import Text.Pandoc.Lua.Util (addFunction) +import Text.Pandoc.Lua.Util (OrNil (OrNil), addFunction) import qualified Data.Digest.Pure.SHA as SHA import qualified Data.ByteString.Lazy as BSL @@ -44,15 +44,32 @@ import qualified Text.Pandoc.Shared as Shared pushModule :: Lua NumResults pushModule = do Lua.newtable + addFunction "hierarchicalize" hierarchicalize + addFunction "normalize_date" normalizeDate addFunction "sha1" sha1 addFunction "stringify" stringify + addFunction "to_roman_numeral" toRomanNumeral return 1 +-- | Convert list of Pandoc blocks into (hierarchical) list of Elements. +hierarchicalize :: [Block] -> Lua [Shared.Element] +hierarchicalize = return . Shared.hierarchicalize + +-- | 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 :: String -> Lua (OrNil String) +normalizeDate = return . OrNil . Shared.normalizeDate + -- | Calculate the hash of the given contents. sha1 :: BSL.ByteString -> Lua String sha1 = return . SHA.showDigest . SHA.sha1 +-- | Convert pandoc structure to a string with formatting removed. +-- Footnotes are skipped (since we don't want their contents in link +-- labels). stringify :: AstElement -> Lua String stringify el = return $ case el of PandocElement pd -> Shared.stringify pd @@ -77,3 +94,7 @@ instance FromLuaStack AstElement where Right x -> return x Left _ -> Lua.throwLuaError "Expected an AST element, but could not parse value as such." + +-- | Convert a number < 4000 to uppercase roman numeral. +toRomanNumeral :: LuaInteger -> Lua String +toRomanNumeral = return . Shared.toRomanNumeral . fromIntegral diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs index ce6dbdb98..119946b78 100644 --- a/src/Text/Pandoc/Lua/StackInstances.hs +++ b/src/Text/Pandoc/Lua/StackInstances.hs @@ -33,13 +33,15 @@ StackValue instances for pandoc types. module Text.Pandoc.Lua.StackInstances () where import Control.Applicative ((<|>)) +import Control.Monad (when) import Foreign.Lua (FromLuaStack (peek), Lua, LuaInteger, LuaNumber, StackIndex, ToLuaStack (push), Type (..), throwLuaError, tryLua) import Text.Pandoc.Definition import Text.Pandoc.Lua.Util (adjustIndexBy, getTable, pushViaConstructor) -import Text.Pandoc.Shared (safeRead) +import Text.Pandoc.Shared (Element (Blk, Sec), safeRead) import qualified Foreign.Lua as Lua +import qualified Text.Pandoc.Lua.Util as LuaUtil instance ToLuaStack Pandoc where push (Pandoc meta blocks) = @@ -306,3 +308,27 @@ instance ToLuaStack LuaAttr where instance FromLuaStack LuaAttr where peek idx = LuaAttr <$> peek idx + +-- +-- Hierarchical elements +-- +instance ToLuaStack Element where + push (Blk blk) = push blk + push (Sec lvl num attr label contents) = do + Lua.newtable + LuaUtil.addValue "level" lvl + LuaUtil.addValue "numbering" num + LuaUtil.addValue "attr" (LuaAttr attr) + LuaUtil.addValue "label" label + LuaUtil.addValue "contents" contents + pushSecMetaTable + Lua.setmetatable (-2) + where + pushSecMetaTable :: Lua () + pushSecMetaTable = do + inexistant <- Lua.newmetatable "PandocElementSec" + when inexistant $ do + LuaUtil.addValue "t" "Sec" + Lua.push "__index" + Lua.pushvalue (-2) + Lua.rawset (-3) diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs index 28d09d339..1f7664fc0 100644 --- a/src/Text/Pandoc/Lua/Util.hs +++ b/src/Text/Pandoc/Lua/Util.hs @@ -125,6 +125,10 @@ instance FromLuaStack a => FromLuaStack (OrNil a) where then return (OrNil Nothing) else OrNil . Just <$> Lua.peek idx +instance ToLuaStack a => ToLuaStack (OrNil a) where + push (OrNil Nothing) = Lua.pushnil + push (OrNil (Just x)) = Lua.push x + -- | Helper class for pushing a single value to the stack via a lua function. -- See @pushViaCall@. class PushViaCall a where |