diff options
Diffstat (limited to 'src/Text/Pandoc/Lua/Module')
| -rw-r--r-- | src/Text/Pandoc/Lua/Module/MediaBag.hs | 14 | ||||
| -rw-r--r-- | src/Text/Pandoc/Lua/Module/Pandoc.hs | 21 | ||||
| -rw-r--r-- | src/Text/Pandoc/Lua/Module/Utils.hs | 37 |
3 files changed, 47 insertions, 25 deletions
diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs index 33c441c99..7d942a452 100644 --- a/src/Text/Pandoc/Lua/Module/MediaBag.hs +++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs @@ -1,5 +1,5 @@ {- -Copyright © 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> +Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -17,7 +17,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Module : Text.Pandoc.Lua.Module.MediaBag - Copyright : Copyright © 2017 Albert Krewinkel + Copyright : Copyright © 2017-2018 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -32,11 +32,11 @@ module Text.Pandoc.Lua.Module.MediaBag import Control.Monad (zipWithM_) import Data.IORef (IORef, modifyIORef', readIORef) import Data.Maybe (fromMaybe) -import Foreign.Lua (Lua, NumResults, liftIO) +import Foreign.Lua (Lua, NumResults, Optional, liftIO) import Text.Pandoc.Class (CommonState (..), fetchItem, putCommonState, runIOorExplode, setMediaBag) import Text.Pandoc.Lua.StackInstances () -import Text.Pandoc.Lua.Util (OrNil (toMaybe), addFunction) +import Text.Pandoc.Lua.Util (addFunction) import Text.Pandoc.MIME (MimeType) import qualified Data.ByteString.Lazy as BL @@ -57,12 +57,12 @@ pushModule commonState mediaBagRef = do insertMediaFn :: IORef MB.MediaBag -> FilePath - -> OrNil MimeType + -> Optional MimeType -> BL.ByteString -> Lua NumResults -insertMediaFn mbRef fp nilOrMime contents = do +insertMediaFn mbRef fp optionalMime contents = do liftIO . modifyIORef' mbRef $ - MB.insertMedia fp (toMaybe nilOrMime) contents + MB.insertMedia fp (Lua.fromOptional optionalMime) contents return 0 lookupMediaFn :: IORef MB.MediaBag diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs index 5b8714e07..f458d4773 100644 --- a/src/Text/Pandoc/Lua/Module/Pandoc.hs +++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs @@ -1,5 +1,5 @@ {- -Copyright © 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> +Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {-# LANGUAGE FlexibleContexts #-} {- | Module : Text.Pandoc.Lua.Module.Pandoc - Copyright : Copyright © 2017 Albert Krewinkel + Copyright : Copyright © 2017-2018 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -34,14 +34,13 @@ import Control.Monad (when) import Data.Default (Default (..)) import Data.Maybe (fromMaybe) import Data.Text (pack) -import Foreign.Lua (ToLuaStack, FromLuaStack, Lua, NumResults, liftIO) +import Foreign.Lua (ToLuaStack, FromLuaStack, Lua, NumResults, Optional, liftIO) import System.Exit (ExitCode (..)) import Text.Pandoc.Class (runIO) import Text.Pandoc.Definition (Block, Inline) import Text.Pandoc.Lua.Filter (walkInlines, walkBlocks, LuaFilter) import Text.Pandoc.Lua.StackInstances () -import Text.Pandoc.Lua.Util (OrNil (toMaybe), addFunction, addValue, - loadScriptFromDataDir, raiseError) +import Text.Pandoc.Lua.Util (addFunction, addValue, loadScriptFromDataDir) import Text.Pandoc.Walk (Walkable) import Text.Pandoc.Options (ReaderOptions (readerExtensions)) import Text.Pandoc.Process (pipeProcess) @@ -72,19 +71,19 @@ walkInline = walkElement walkBlock :: Block -> LuaFilter -> Lua Block walkBlock = walkElement -readDoc :: String -> OrNil String -> Lua NumResults +readDoc :: String -> Optional String -> Lua NumResults readDoc content formatSpecOrNil = do - let formatSpec = fromMaybe "markdown" (toMaybe formatSpecOrNil) + let formatSpec = fromMaybe "markdown" (Lua.fromOptional formatSpecOrNil) case getReader formatSpec of - Left s -> raiseError s -- Unknown reader + Left s -> Lua.raiseError s -- Unknown reader Right (reader, es) -> case reader of TextReader r -> do res <- liftIO $ runIO $ r def{ readerExtensions = es } (pack content) case res of Right pd -> (1 :: NumResults) <$ Lua.push pd -- success, push Pandoc - Left s -> raiseError (show s) -- error while reading - _ -> raiseError "Only string formats are supported at the moment." + Left s -> Lua.raiseError (show s) -- error while reading + _ -> Lua.raiseError "Only string formats are supported at the moment." -- | Pipes input through a command. pipeFn :: String @@ -95,7 +94,7 @@ pipeFn command args input = do (ec, output) <- liftIO $ pipeProcess Nothing command args input case ec of ExitSuccess -> 1 <$ Lua.push output - ExitFailure n -> raiseError (PipeError command n output) + ExitFailure n -> Lua.raiseError (PipeError command n output) data PipeError = PipeError { pipeErrorCommand :: String diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs index c0d7397ce..f8eb96dc7 100644 --- a/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/src/Text/Pandoc/Lua/Module/Utils.hs @@ -1,5 +1,5 @@ {- -Copyright © 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> +Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -17,7 +17,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Module : Text.Pandoc.Lua.Module.Utils - Copyright : Copyright © 2017 Albert Krewinkel + Copyright : Copyright © 2017-2018 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -30,22 +30,26 @@ module Text.Pandoc.Lua.Module.Utils ) where import Control.Applicative ((<|>)) +import Data.Default (def) import Foreign.Lua (FromLuaStack, Lua, LuaInteger, NumResults) +import Text.Pandoc.Class (runIO, setUserDataDir) import Text.Pandoc.Definition (Pandoc, Meta, MetaValue, Block, Inline) import Text.Pandoc.Lua.StackInstances () -import Text.Pandoc.Lua.Util (OrNil (OrNil), addFunction) +import Text.Pandoc.Lua.Util (addFunction, popValue) 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.Filter.JSON as JSONFilter import qualified Text.Pandoc.Shared as Shared -- | Push the "pandoc.utils" module to the lua stack. -pushModule :: Lua NumResults -pushModule = do +pushModule :: Maybe FilePath -> Lua NumResults +pushModule mbDatadir = do Lua.newtable addFunction "hierarchicalize" hierarchicalize addFunction "normalize_date" normalizeDate + addFunction "run_json_filter" (runJSONFilter mbDatadir) addFunction "sha1" sha1 addFunction "stringify" stringify addFunction "to_roman_numeral" toRomanNumeral @@ -59,8 +63,27 @@ hierarchicalize = return . Shared.hierarchicalize -- 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 +normalizeDate :: String -> Lua (Lua.Optional String) +normalizeDate = return . Lua.Optional . Shared.normalizeDate + +-- | Run a JSON filter on the given document. +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" + (:[]) <$> 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 -- | Calculate the hash of the given contents. sha1 :: BSL.ByteString |
