aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Marshal
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Marshal')
-rw-r--r--src/Text/Pandoc/Lua/Marshal/CommonState.hs70
-rw-r--r--src/Text/Pandoc/Lua/Marshal/Context.hs28
-rw-r--r--src/Text/Pandoc/Lua/Marshal/PandocError.hs51
-rw-r--r--src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs133
-rw-r--r--src/Text/Pandoc/Lua/Marshal/Reference.hs107
-rw-r--r--src/Text/Pandoc/Lua/Marshal/Sources.hs46
6 files changed, 435 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Lua/Marshal/CommonState.hs b/src/Text/Pandoc/Lua/Marshal/CommonState.hs
new file mode 100644
index 000000000..a8c0e28d2
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/CommonState.hs
@@ -0,0 +1,70 @@
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshal.CommonState
+ Copyright : © 2012-2021 John MacFarlane
+ © 2017-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Instances to marshal (push) and unmarshal (peek) the common state.
+-}
+module Text.Pandoc.Lua.Marshal.CommonState
+ ( typeCommonState
+ , peekCommonState
+ , pushCommonState
+ ) where
+
+import HsLua.Core
+import HsLua.Marshalling
+import HsLua.Packaging
+import Text.Pandoc.Class (CommonState (..))
+import Text.Pandoc.Logging (LogMessage, showLogMessage)
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+
+-- | Lua type used for the @CommonState@ object.
+typeCommonState :: LuaError e => DocumentedType e CommonState
+typeCommonState = deftype "pandoc CommonState" []
+ [ readonly "input_files" "input files passed to pandoc"
+ (pushPandocList pushString, stInputFiles)
+
+ , readonly "output_file" "the file to which pandoc will write"
+ (maybe pushnil pushString, stOutputFile)
+
+ , readonly "log" "list of log messages"
+ (pushPandocList (pushUD typeLogMessage), stLog)
+
+ , readonly "request_headers" "headers to add for HTTP requests"
+ (pushPandocList (pushPair pushText pushText), stRequestHeaders)
+
+ , readonly "resource_path"
+ "path to search for resources like included images"
+ (pushPandocList pushString, stResourcePath)
+
+ , readonly "source_url" "absolute URL + dir of 1st source file"
+ (maybe pushnil pushText, stSourceURL)
+
+ , readonly "user_data_dir" "directory to search for data files"
+ (maybe pushnil pushString, stUserDataDir)
+
+ , readonly "trace" "controls whether tracing messages are issued"
+ (pushBool, stTrace)
+
+ , readonly "verbosity" "verbosity level"
+ (pushString . show, stVerbosity)
+ ]
+
+peekCommonState :: LuaError e => Peeker e CommonState
+peekCommonState = peekUD typeCommonState
+
+pushCommonState :: LuaError e => Pusher e CommonState
+pushCommonState = pushUD typeCommonState
+
+typeLogMessage :: LuaError e => DocumentedType e LogMessage
+typeLogMessage = deftype "pandoc LogMessage"
+ [ operation Index $ defun "__tostring"
+ ### liftPure showLogMessage
+ <#> udparam typeLogMessage "msg" "object"
+ =#> functionResult pushText "string" "stringified log message"
+ ]
+ mempty -- no members
diff --git a/src/Text/Pandoc/Lua/Marshal/Context.hs b/src/Text/Pandoc/Lua/Marshal/Context.hs
new file mode 100644
index 000000000..17af936e1
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/Context.hs
@@ -0,0 +1,28 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshaling.Context
+ Copyright : © 2012-2021 John MacFarlane
+ © 2017-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Marshaling instance for doctemplates Context and its components.
+-}
+module Text.Pandoc.Lua.Marshal.Context () where
+
+import qualified HsLua as Lua
+import HsLua (Pushable)
+import Text.DocTemplates (Context(..), Val(..), TemplateTarget)
+import Text.DocLayout (render)
+
+instance (TemplateTarget a, Pushable a) => Pushable (Context a) where
+ push (Context m) = Lua.push m
+
+instance (TemplateTarget a, Pushable a) => Pushable (Val a) where
+ push NullVal = Lua.push ()
+ push (BoolVal b) = Lua.push b
+ push (MapVal ctx) = Lua.push ctx
+ push (ListVal xs) = Lua.push xs
+ push (SimpleVal d) = Lua.push $ render Nothing d
diff --git a/src/Text/Pandoc/Lua/Marshal/PandocError.hs b/src/Text/Pandoc/Lua/Marshal/PandocError.hs
new file mode 100644
index 000000000..d1c0ad4f4
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/PandocError.hs
@@ -0,0 +1,51 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshal.PandocError
+ Copyright : © 2020-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Marshal of @'PandocError'@ values.
+-}
+module Text.Pandoc.Lua.Marshal.PandocError
+ ( peekPandocError
+ , pushPandocError
+ , typePandocError
+ )
+ where
+
+import HsLua.Core (LuaError)
+import HsLua.Marshalling (Peeker, Pusher, pushString, liftLua)
+import HsLua.Packaging
+import Text.Pandoc.Error (PandocError (PandocLuaError))
+
+import qualified HsLua as Lua
+import qualified Text.Pandoc.UTF8 as UTF8
+
+-- | Lua userdata type definition for PandocError.
+typePandocError :: LuaError e => DocumentedType e PandocError
+typePandocError = deftype "PandocError"
+ [ operation Tostring $ defun "__tostring"
+ ### liftPure (show @PandocError)
+ <#> udparam typePandocError "obj" "PandocError object"
+ =#> functionResult pushString "string" "string representation of error."
+ ]
+ mempty -- no members
+
+-- | Peek a @'PandocError'@ element to the Lua stack.
+pushPandocError :: LuaError e => Pusher e PandocError
+pushPandocError = pushUD typePandocError
+
+-- | Retrieve a @'PandocError'@ from the Lua stack.
+peekPandocError :: LuaError e => Peeker e PandocError
+peekPandocError idx = Lua.retrieving "PandocError" $
+ liftLua (Lua.ltype idx) >>= \case
+ Lua.TypeUserdata -> peekUD typePandocError idx
+ _ -> do
+ msg <- liftLua $ Lua.state >>= \l -> Lua.liftIO (Lua.popErrorMessage l)
+ return $ PandocLuaError (UTF8.toText msg)
diff --git a/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs b/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs
new file mode 100644
index 000000000..c20770dba
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/ReaderOptions.hs
@@ -0,0 +1,133 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshaling.ReaderOptions
+ Copyright : © 2012-2021 John MacFarlane
+ © 2017-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Marshaling instance for ReaderOptions and its components.
+-}
+module Text.Pandoc.Lua.Marshal.ReaderOptions
+ ( peekReaderOptions
+ , pushReaderOptions
+ , pushReaderOptionsReadonly
+ ) where
+
+import Data.Default (def)
+import HsLua as Lua
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+import Text.Pandoc.Options (ReaderOptions (..))
+
+--
+-- Reader Options
+--
+
+-- | Retrieve a ReaderOptions value, either from a normal ReaderOptions
+-- value, from a read-only object, or from a table with the same
+-- keys as a ReaderOptions object.
+peekReaderOptions :: LuaError e => Peeker e ReaderOptions
+peekReaderOptions = retrieving "ReaderOptions" . \idx ->
+ liftLua (ltype idx) >>= \case
+ TypeUserdata -> choice [ peekUD typeReaderOptions
+ , peekUD typeReaderOptionsReadonly
+ ]
+ idx
+ TypeTable -> peekReaderOptionsTable idx
+ _ -> failPeek =<<
+ typeMismatchMessage "ReaderOptions userdata or table" idx
+
+-- | Pushes a ReaderOptions value as userdata object.
+pushReaderOptions :: LuaError e => Pusher e ReaderOptions
+pushReaderOptions = pushUD typeReaderOptions
+
+-- | Pushes a ReaderOptions object, but makes it read-only.
+pushReaderOptionsReadonly :: LuaError e => Pusher e ReaderOptions
+pushReaderOptionsReadonly = pushUD typeReaderOptionsReadonly
+
+-- | ReaderOptions object type for read-only values.
+typeReaderOptionsReadonly :: LuaError e => DocumentedType e ReaderOptions
+typeReaderOptionsReadonly = deftype "ReaderOptions (read-only)"
+ [ operation Tostring $ lambda
+ ### liftPure show
+ <#> udparam typeReaderOptions "opts" "options to print in native format"
+ =#> functionResult pushString "string" "Haskell representation"
+ , operation Newindex $ lambda
+ ### (failLua "This ReaderOptions value is read-only.")
+ =?> "Throws an error when called, i.e., an assignment is made."
+ ]
+ readerOptionsMembers
+
+-- | 'ReaderOptions' object type.
+typeReaderOptions :: LuaError e => DocumentedType e ReaderOptions
+typeReaderOptions = deftype "ReaderOptions"
+ [ operation Tostring $ lambda
+ ### liftPure show
+ <#> udparam typeReaderOptions "opts" "options to print in native format"
+ =#> functionResult pushString "string" "Haskell representation"
+ ]
+ readerOptionsMembers
+
+-- | Member properties of 'ReaderOptions' Lua values.
+readerOptionsMembers :: LuaError e
+ => [Member e (DocumentedFunction e) ReaderOptions]
+readerOptionsMembers =
+ [ property "abbreviations" ""
+ (pushSet pushText, readerAbbreviations)
+ (peekSet peekText, \opts x -> opts{ readerAbbreviations = x })
+ , property "columns" ""
+ (pushIntegral, readerColumns)
+ (peekIntegral, \opts x -> opts{ readerColumns = x })
+ , property "default_image_extension" ""
+ (pushText, readerDefaultImageExtension)
+ (peekText, \opts x -> opts{ readerDefaultImageExtension = x })
+ , property "extensions" ""
+ (pushString . show, readerExtensions)
+ (peekRead, \opts x -> opts{ readerExtensions = x })
+ , property "indented_code_classes" ""
+ (pushPandocList pushText, readerIndentedCodeClasses)
+ (peekList peekText, \opts x -> opts{ readerIndentedCodeClasses = x })
+ , property "strip_comments" ""
+ (pushBool, readerStripComments)
+ (peekBool, \opts x -> opts{ readerStripComments = x })
+ , property "standalone" ""
+ (pushBool, readerStandalone)
+ (peekBool, \opts x -> opts{ readerStandalone = x })
+ , property "tab_stop" ""
+ (pushIntegral, readerTabStop)
+ (peekIntegral, \opts x -> opts{ readerTabStop = x })
+ , property "track_changes" ""
+ (pushString . show, readerTrackChanges)
+ (peekRead, \opts x -> opts{ readerTrackChanges = x })
+ ]
+
+-- | Retrieves a 'ReaderOptions' object from a table on the stack, using
+-- the default values for all missing fields.
+--
+-- Internally, this pushes the default reader options, sets each
+-- key/value pair of the table in the userdata value, then retrieves the
+-- object again. This will update all fields and complain about unknown
+-- keys.
+peekReaderOptionsTable :: LuaError e => Peeker e ReaderOptions
+peekReaderOptionsTable idx = retrieving "ReaderOptions (table)" $ do
+ liftLua $ do
+ absidx <- absindex idx
+ pushUD typeReaderOptions def
+ let setFields = do
+ next absidx >>= \case
+ False -> return () -- all fields were copied
+ True -> do
+ pushvalue (nth 2) *> insert (nth 2)
+ settable (nth 4) -- set in userdata object
+ setFields
+ pushnil -- first key
+ setFields
+ peekUD typeReaderOptions top
+
+instance Pushable ReaderOptions where
+ push = pushReaderOptions
diff --git a/src/Text/Pandoc/Lua/Marshal/Reference.hs b/src/Text/Pandoc/Lua/Marshal/Reference.hs
new file mode 100644
index 000000000..ee297484e
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/Reference.hs
@@ -0,0 +1,107 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+ Module : Text.Pandoc.Lua.Marshaling.ReaderOptions
+ Copyright : © 2012-2021 John MacFarlane
+ © 2017-2021 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+ Stability : alpha
+
+Marshal citeproc 'Reference' values.
+-}
+module Text.Pandoc.Lua.Marshal.Reference
+ ( pushReference
+ ) where
+
+import Citeproc.Types
+ ( Date (..), DateParts (..), ItemId (..), Name (..), Reference (..)
+ , Val (..), Variable, fromVariable
+ )
+import Control.Monad (forM_)
+import HsLua hiding (Name, Reference, pushName, peekName)
+import Text.Pandoc.Builder (Inlines, toList)
+import Text.Pandoc.Lua.Marshal.Inline (pushInlines)
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+
+import qualified Data.Map as Map
+import qualified HsLua
+
+-- | Pushes a ReaderOptions value as userdata object.
+pushReference :: LuaError e => Pusher e (Reference Inlines)
+pushReference reference = do
+ pushAsTable [ ("id", pushItemId . referenceId)
+ , ("type", pushText . referenceType)
+ ]
+ reference
+ forM_ (Map.toList $ referenceVariables reference) $ \(var, val) -> do
+ pushVariable var
+ pushVal val
+ rawset (nth 3)
+
+-- | Pushes an 'ItemId' as a string.
+pushItemId :: Pusher e ItemId
+pushItemId = pushText . unItemId
+
+-- | Pushes a person's 'Name' as a table.
+pushName :: LuaError e => Pusher e Name
+pushName = pushAsTable
+ [ ("family" , pushTextOrNil . nameFamily)
+ , ("given" , pushTextOrNil . nameGiven)
+ , ("dropping-particle" , pushTextOrNil . nameDroppingParticle)
+ , ("non-dropping-particle" , pushTextOrNil . nameNonDroppingParticle)
+ , ("suffix" , pushTextOrNil . nameSuffix)
+ , ("literal" , pushTextOrNil . nameLiteral)
+ , ("comma-suffix" , pushBoolOrNil . nameCommaSuffix)
+ , ("static-ordering" , pushBoolOrNil . nameStaticOrdering)
+ ]
+ where
+ pushTextOrNil = \case
+ Nothing -> pushnil
+ Just xs -> pushText xs
+
+-- | Pushes a boolean, but uses @nil@ instead of @false@; table fields
+-- are not set unless the value is true.
+pushBoolOrNil :: Pusher e Bool
+pushBoolOrNil = \case
+ False -> pushnil
+ True -> pushBool True
+
+-- | Pushes a 'Variable' as string.
+pushVariable :: Pusher e Variable
+pushVariable = pushText . fromVariable
+
+-- | Pushes a 'Val', i.e., a variable value.
+pushVal :: LuaError e => Pusher e (Val Inlines)
+pushVal = \case
+ TextVal t -> pushText t
+ FancyVal inlns -> pushInlines $ toList inlns
+ NumVal i -> pushIntegral i
+ NamesVal names -> pushPandocList pushName names
+ DateVal date -> pushDate date
+
+-- | Pushes a 'Date' as table.
+pushDate :: LuaError e => Pusher e Date
+pushDate = pushAsTable
+ [ ("date-parts", pushPandocList pushDateParts . dateParts)
+ , ("circa", pushBoolOrNil . dateCirca)
+ , ("season", maybe pushnil pushIntegral . dateSeason)
+ , ("literal", maybe pushnil pushText . dateLiteral)
+ ]
+ where
+ -- date parts are lists of Int values
+ pushDateParts (DateParts dp) = pushPandocList pushIntegral dp
+
+-- | Helper funtion to push an object as a table.
+pushAsTable :: LuaError e
+ => [(HsLua.Name, a -> LuaE e ())]
+ -> a -> LuaE e ()
+pushAsTable props obj = do
+ createtable 0 (length props)
+ forM_ props $ \(name, pushValue) -> do
+ HsLua.pushName name
+ pushValue obj
+ rawset (nth 3)
diff --git a/src/Text/Pandoc/Lua/Marshal/Sources.hs b/src/Text/Pandoc/Lua/Marshal/Sources.hs
new file mode 100644
index 000000000..7b5262ab5
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshal/Sources.hs
@@ -0,0 +1,46 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{- |
+Module : Text.Pandoc.Lua.Marshaling.Sources
+Copyright : © 2021 Albert Krewinkel
+License : GNU GPL, version 2 or above
+Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+
+Marshal 'Sources'.
+-}
+module Text.Pandoc.Lua.Marshal.Sources
+ ( pushSources
+ ) where
+
+import Data.Text (Text)
+import HsLua as Lua
+import Text.Pandoc.Lua.Marshal.List (newListMetatable)
+import Text.Pandoc.Sources (Sources (..))
+import Text.Parsec (SourcePos, sourceName)
+
+-- | Pushes the 'Sources' as a list of lazy Lua objects.
+pushSources :: LuaError e => Pusher e Sources
+pushSources (Sources srcs) = do
+ pushList (pushUD typeSource) srcs
+ newListMetatable "pandoc Sources" $ do
+ pushName "__tostring"
+ pushHaskellFunction $ do
+ sources <- forcePeek $ peekList (peekUD typeSource) (nthBottom 1)
+ pushText . mconcat $ map snd sources
+ return 1
+ rawset (nth 3)
+ setmetatable (nth 2)
+
+-- | Source object type.
+typeSource :: LuaError e => DocumentedType e (SourcePos, Text)
+typeSource = deftype "pandoc input source"
+ [ operation Tostring $ lambda
+ ### liftPure snd
+ <#> udparam typeSource "srcs" "Source to print in native format"
+ =#> functionResult pushText "string" "Haskell representation"
+ ]
+ [ readonly "name" "source name"
+ (pushString, sourceName . fst)
+ , readonly "text" "source text"
+ (pushText, snd)
+ ]