{-# LANGUAGE NoImplicitPrelude #-}
module Text.Pandoc.Lua.Module.Utils
( pushModule
) where
import Prelude
import Control.Applicative ((<|>))
import Data.Char (toLower)
import Data.Default (def)
import Data.Version (Version)
import Foreign.Lua (Peekable, Lua, NumResults)
import Text.Pandoc.Class (runIO, setUserDataDir)
import Text.Pandoc.Definition ( Pandoc, Meta, MetaValue (..), Block, Inline
, Citation, Attr, ListAttributes)
import Text.Pandoc.Lua.Marshaling ()
import Text.Pandoc.Lua.Util (addFunction)
import qualified Data.Digest.Pure.SHA as SHA
import qualified Data.ByteString.Lazy as BSL
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
pushModule :: Maybe FilePath -> Lua NumResults
pushModule mbDatadir = do
Lua.newtable
addFunction "blocks_to_inlines" blocksToInlines
addFunction "equals" equals
addFunction "hierarchicalize" hierarchicalize
addFunction "normalize_date" normalizeDate
addFunction "run_json_filter" (runJSONFilter mbDatadir)
addFunction "sha1" sha1
addFunction "stringify" stringify
addFunction "to_roman_numeral" toRomanNumeral
addFunction "Version" (return :: Version -> Lua Version)
return 1
blocksToInlines :: [Block] -> Lua.Optional [Inline] -> Lua [Inline]
blocksToInlines blks optSep = do
let sep = case Lua.fromOptional optSep of
Just x -> B.fromList x
Nothing -> Shared.defaultBlocksSeparator
return $ B.toList (Shared.blocksToInlinesWithSep sep blks)
hierarchicalize :: [Block] -> Lua [Shared.Element]
hierarchicalize = return . Shared.hierarchicalize
normalizeDate :: String -> Lua (Lua.Optional String)
normalizeDate = return . Lua.Optional . Shared.normalizeDate
runJSONFilter :: Maybe FilePath
-> Pandoc
-> FilePath
-> Lua.Optional [String]
-> Lua NumResults
runJSONFilter mbDatadir doc filterFile optArgs = do
args <- case Lua.fromOptional optArgs of
Just x -> return x
Nothing -> do
Lua.getglobal "FORMAT"
(:[]) <$> Lua.popValue
filterRes <- Lua.liftIO . runIO $ do
setUserDataDir mbDatadir
JSONFilter.apply def args filterFile doc
case filterRes of
Left err -> Lua.raiseError (show err)
Right d -> (1 :: NumResults) <$ Lua.push d
sha1 :: BSL.ByteString
-> Lua String
sha1 = return . SHA.showDigest . SHA.sha1
stringify :: AstElement -> Lua String
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
_ -> ""
stringifyMetaValue :: MetaValue -> String
stringifyMetaValue mv = case mv of
MetaBool b -> map toLower (show b)
MetaString s -> s
_ -> Shared.stringify mv
equals :: AstElement -> AstElement -> Lua 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 <- Lua.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 _ -> Lua.throwException
"Expected an AST element, but could not parse value as such."
toRomanNumeral :: Lua.Integer -> Lua String
toRomanNumeral = return . Shared.toRomanNumeral . fromIntegral