diff options
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r-- | src/Text/Pandoc/Lua/Filter.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Init.hs | 11 | ||||
-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 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Packages.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/StackInstances.hs | 102 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Util.hs | 33 |
8 files changed, 156 insertions, 77 deletions
diff --git a/src/Text/Pandoc/Lua/Filter.hs b/src/Text/Pandoc/Lua/Filter.hs index 9e109bb52..cc2b9d47e 100644 --- a/src/Text/Pandoc/Lua/Filter.hs +++ b/src/Text/Pandoc/Lua/Filter.hs @@ -11,6 +11,7 @@ module Text.Pandoc.Lua.Filter ( LuaFilterFunction , inlineElementNames ) where import Control.Monad (mplus, unless, when, (>=>)) +import Control.Monad.Catch (finally) import Text.Pandoc.Definition import Data.Foldable (foldrM) import Data.Map (Map) @@ -22,6 +23,7 @@ import Text.Pandoc.Walk (walkM, Walkable) import Data.Data (Data, DataType, dataTypeConstrs, dataTypeName, dataTypeOf, showConstr, toConstr, tyconUQname) import Text.Pandoc.Lua.StackInstances() +import Text.Pandoc.Lua.Util (typeCheck) type FunctionMap = Map String LuaFilterFunction @@ -65,7 +67,7 @@ registerFilterFunction idx = do elementOrList :: FromLuaStack a => a -> Lua [a] elementOrList x = do - let topOfStack = Lua.StackIndex (-1) + let topOfStack = Lua.stackTop elementUnchanged <- Lua.isnil topOfStack if elementUnchanged then [x] <$ Lua.pop 1 @@ -73,7 +75,9 @@ elementOrList x = do mbres <- Lua.peekEither topOfStack case mbres of Right res -> [res] <$ Lua.pop 1 - Left _ -> Lua.toList topOfStack <* Lua.pop 1 + Left _ -> do + typeCheck Lua.stackTop Lua.TypeTable + Lua.toList topOfStack `finally` Lua.pop 1 -- | Try running a filter for the given element tryFilter :: (Data a, FromLuaStack a, ToLuaStack a) diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs index 9b107e945..f3ee2caf1 100644 --- a/src/Text/Pandoc/Lua/Init.hs +++ b/src/Text/Pandoc/Lua/Init.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 - 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> @@ -35,10 +35,13 @@ module Text.Pandoc.Lua.Init import Control.Monad.Trans (MonadIO (..)) import Data.IORef (newIORef, readIORef) +import Data.Version (Version (versionBranch)) import Foreign.Lua (Lua, LuaException (..)) import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8) +import Paths_pandoc (version) import Text.Pandoc.Class (PandocIO, getCommonState, getUserDataDir, getMediaBag, setMediaBag) +import Text.Pandoc.Definition (pandocTypesVersion) import Text.Pandoc.Lua.Packages (LuaPackageParams (..), installPandocPackageSearcher) import Text.Pandoc.Lua.Util (loadScriptFromDataDir) @@ -75,5 +78,9 @@ initLuaState :: LuaPackageParams -> Lua () initLuaState luaPkgParams = do Lua.openlibs Lua.preloadTextModule "text" + Lua.push (versionBranch version) + Lua.setglobal "PANDOC_VERSION" + Lua.push (versionBranch pandocTypesVersion) + Lua.setglobal "PANDOC_API_VERSION" installPandocPackageSearcher luaPkgParams loadScriptFromDataDir (luaPkgDataDir luaPkgParams) "init.lua" 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 diff --git a/src/Text/Pandoc/Lua/Packages.hs b/src/Text/Pandoc/Lua/Packages.hs index f26c17084..0169d0045 100644 --- a/src/Text/Pandoc/Lua/Packages.hs +++ b/src/Text/Pandoc/Lua/Packages.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 @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {-# LANGUAGE FlexibleContexts #-} {- | Module : Text.Pandoc.Lua.Packages - 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> @@ -78,7 +78,8 @@ pandocPackageSearcher luaPkgParams pkgName = "pandoc.mediabag" -> let st = luaPkgCommonState luaPkgParams mbRef = luaPkgMediaBag luaPkgParams in pushWrappedHsFun (MediaBag.pushModule st mbRef) - "pandoc.utils" -> pushWrappedHsFun Utils.pushModule + "pandoc.utils" -> let datadirMb = luaPkgDataDir luaPkgParams + in pushWrappedHsFun (Utils.pushModule datadirMb) _ -> searchPureLuaLoader where pushWrappedHsFun f = do diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs index 119946b78..38404157c 100644 --- a/src/Text/Pandoc/Lua/StackInstances.hs +++ b/src/Text/Pandoc/Lua/StackInstances.hs @@ -1,6 +1,6 @@ {- -Copyright © 2012-2017 John MacFarlane <jgm@berkeley.edu> - 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> +Copyright © 2012-2018 John MacFarlane <jgm@berkeley.edu> + 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 @@ -16,13 +16,14 @@ You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Text.Pandoc.Lua.StackInstances - Copyright : © 2012-2017 John MacFarlane - © 2017 Albert Krewinkel + Copyright : © 2012-2018 John MacFarlane + © 2017-2018 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -34,30 +35,43 @@ module Text.Pandoc.Lua.StackInstances () where import Control.Applicative ((<|>)) import Control.Monad (when) +import Control.Monad.Catch (finally) +import Data.Data (showConstr, toConstr) +import Data.Foldable (forM_) 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.Extensions (Extensions) +import Text.Pandoc.Lua.Util (adjustIndexBy, getTable, pushViaConstructor, + typeCheck) +import Text.Pandoc.Options (ReaderOptions (..), TrackChanges) import Text.Pandoc.Shared (Element (Blk, Sec), safeRead) import qualified Foreign.Lua as Lua +import qualified Data.Set as Set import qualified Text.Pandoc.Lua.Util as LuaUtil +defineHowTo :: String -> Lua a -> Lua a +defineHowTo ctx op = op `Lua.modifyLuaError` (("Could not " ++ ctx ++ ": ") ++) + instance ToLuaStack Pandoc where push (Pandoc meta blocks) = pushViaConstructor "Pandoc" blocks meta instance FromLuaStack Pandoc where - peek idx = do + peek idx = defineHowTo "get Pandoc value" $ do + typeCheck idx Lua.TypeTable blocks <- getTable idx "blocks" - meta <- getTable idx "meta" + meta <- Lua.getfield idx "meta" *> (Lua.peek Lua.stackTop `finally` Lua.pop 1) return $ Pandoc meta blocks instance ToLuaStack Meta where push (Meta mmap) = pushViaConstructor "Meta" mmap instance FromLuaStack Meta where - peek idx = Meta <$> peek idx + peek idx = defineHowTo "get Meta value" $ do + typeCheck idx Lua.TypeTable + Meta <$> peek idx instance ToLuaStack MetaValue where push = pushMetaValue @@ -84,12 +98,12 @@ instance ToLuaStack Citation where instance FromLuaStack Citation where peek idx = do - id' <- getTable idx "citationId" - prefix <- getTable idx "citationPrefix" - suffix <- getTable idx "citationSuffix" - mode <- getTable idx "citationMode" - num <- getTable idx "citationNoteNum" - hash <- getTable idx "citationHash" + id' <- getTable idx "id" + prefix <- getTable idx "prefix" + suffix <- getTable idx "suffix" + mode <- getTable idx "mode" + num <- getTable idx "note_num" + hash <- getTable idx "hash" return $ Citation id' prefix suffix mode num hash instance ToLuaStack Alignment where @@ -154,7 +168,7 @@ pushMetaValue = \case -- | Interpret the value at the given stack index as meta value. peekMetaValue :: StackIndex -> Lua MetaValue -peekMetaValue idx = do +peekMetaValue idx = defineHowTo "get MetaValue" $ do -- Get the contents of an AST element. let elementContent :: FromLuaStack a => Lua a elementContent = peek idx @@ -203,7 +217,8 @@ pushBlock = \case -- | Return the value at the given index as block if possible. peekBlock :: StackIndex -> Lua Block -peekBlock idx = do +peekBlock idx = defineHowTo "get Block value" $ do + typeCheck idx Lua.TypeTable tag <- getTag idx case tag of "BlockQuote" -> BlockQuote <$> elementContent @@ -254,7 +269,8 @@ pushInline = \case -- | Return the value at the given index as inline if possible. peekInline :: StackIndex -> Lua Inline -peekInline idx = do +peekInline idx = defineHowTo "get Inline value" $ do + typeCheck idx Lua.TypeTable tag <- getTag idx case tag of "Cite" -> uncurry Cite <$> elementContent @@ -290,11 +306,7 @@ getTag idx = do hasMT <- Lua.getmetatable idx push "tag" if hasMT then Lua.rawget (-2) else Lua.rawget (idx `adjustIndexBy` 1) - r <- tryLua (peek (-1)) - Lua.settop top - case r of - Left (Lua.LuaException err) -> throwLuaError err - Right res -> return res + peek Lua.stackTop `finally` Lua.settop top withAttr :: (Attr -> a -> b) -> (LuaAttr, a) -> b withAttr f (attributes, x) = f (fromLuaAttr attributes) x @@ -307,7 +319,7 @@ instance ToLuaStack LuaAttr where pushViaConstructor "Attr" id' classes kv instance FromLuaStack LuaAttr where - peek idx = LuaAttr <$> peek idx + peek idx = defineHowTo "get Attr value" (LuaAttr <$> peek idx) -- -- Hierarchical elements @@ -332,3 +344,43 @@ instance ToLuaStack Element where Lua.push "__index" Lua.pushvalue (-2) Lua.rawset (-3) + + +-- +-- Reader Options +-- +instance ToLuaStack Extensions where + push exts = push (show exts) + +instance ToLuaStack TrackChanges where + push = push . showConstr . toConstr + +instance ToLuaStack a => ToLuaStack (Set.Set a) where + push set = do + Lua.newtable + forM_ set (`LuaUtil.addValue` True) + +instance ToLuaStack ReaderOptions where + push ro = do + let ReaderOptions + (extensions :: Extensions) + (standalone :: Bool) + (columns :: Int) + (tabStop :: Int) + (indentedCodeClasses :: [String]) + (abbreviations :: Set.Set String) + (defaultImageExtension :: String) + (trackChanges :: TrackChanges) + (stripComments :: Bool) + = ro + Lua.newtable + LuaUtil.addValue "extensions" extensions + LuaUtil.addValue "standalone" standalone + LuaUtil.addValue "columns" columns + LuaUtil.addValue "tabStop" tabStop + LuaUtil.addValue "indentedCodeClasses" indentedCodeClasses + LuaUtil.addValue "abbreviations" abbreviations + LuaUtil.addValue "defaultImageExtension" defaultImageExtension + LuaUtil.addValue "trackChanges" trackChanges + LuaUtil.addValue "stripComments" stripComments + diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs index 2958bd734..a3af155c9 100644 --- a/src/Text/Pandoc/Lua/Util.hs +++ b/src/Text/Pandoc/Lua/Util.hs @@ -1,6 +1,6 @@ {- -Copyright © 2012-2017 John MacFarlane <jgm@berkeley.edu> - 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> +Copyright © 2012-2018 John MacFarlane <jgm@berkeley.edu> + 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 @@ -19,8 +19,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {-# LANGUAGE FlexibleInstances #-} {- | Module : Text.Pandoc.Lua.Util - Copyright : © 2012–2017 John MacFarlane, - © 2017 Albert Krewinkel + Copyright : © 2012–2018 John MacFarlane, + © 2017-2018 Albert Krewinkel License : GNU GPL, version 2 or above Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -36,9 +36,9 @@ module Text.Pandoc.Lua.Util , getRawInt , setRawInt , addRawInt + , typeCheck , raiseError , popValue - , OrNil (..) , PushViaCall , pushViaCall , pushViaConstructor @@ -101,6 +101,14 @@ setRawInt idx key value = do addRawInt :: ToLuaStack a => Int -> a -> Lua () addRawInt = setRawInt (-1) +typeCheck :: StackIndex -> Lua.Type -> Lua () +typeCheck idx expected = do + actual <- Lua.ltype idx + when (actual /= expected) $ do + expName <- Lua.typename expected + actName <- Lua.typename actual + Lua.throwLuaError $ "expected " ++ expName ++ " but got " ++ actName ++ "." + raiseError :: ToLuaStack a => a -> Lua NumResults raiseError e = do Lua.push e @@ -115,21 +123,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 |