diff options
-rw-r--r-- | src/Text/Pandoc/Lua/Module/MediaBag.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Pandoc.hs | 17 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Utils.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Util.hs | 16 |
4 files changed, 16 insertions, 33 deletions
diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs index 33c441c99..9dd0a046d 100644 --- a/src/Text/Pandoc/Lua/Module/MediaBag.hs +++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs @@ -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..a10bd3217 100644 --- a/src/Text/Pandoc/Lua/Module/Pandoc.hs +++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs @@ -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..e4ed409b3 100644 --- a/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/src/Text/Pandoc/Lua/Module/Utils.hs @@ -33,7 +33,7 @@ import Control.Applicative ((<|>)) import Foreign.Lua (FromLuaStack, Lua, LuaInteger, NumResults) 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) import qualified Data.Digest.Pure.SHA as SHA import qualified Data.ByteString.Lazy as BSL @@ -59,8 +59,8 @@ 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 -- | Calculate the hash of the given contents. sha1 :: BSL.ByteString diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs index 2958bd734..6b46cfc62 100644 --- a/src/Text/Pandoc/Lua/Util.hs +++ b/src/Text/Pandoc/Lua/Util.hs @@ -38,7 +38,6 @@ module Text.Pandoc.Lua.Util , addRawInt , raiseError , popValue - , OrNil (..) , PushViaCall , pushViaCall , pushViaConstructor @@ -115,21 +114,6 @@ popValue = do Left err -> Lua.throwLuaError err Right x -> return x --- | Newtype wrapper intended to be used for optional Lua values. Nesting this --- type is strongly discouraged and will likely lead to a wrong result. -newtype OrNil a = OrNil { toMaybe :: Maybe a } - -instance FromLuaStack a => FromLuaStack (OrNil a) where - peek idx = do - noValue <- Lua.isnoneornil idx - if noValue - 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 |